SURFEX v8.1
General documentation of Surfex
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 loo1s
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 ! 02/2016: replace DOUBLE PRECISION by REAL to handle problem for promotion of real with GMKPACK or IBM SP
28 ! 06/2016 S.Senesi Use XIOS for diags output
29 ! -------------------------------------------------
30 !
32 !
33 USE modd_type_date_surf, ONLY : date
34 !
36 !
37 USE modd_forc_atm, ONLY: csv ,&! name of all scalar variables
38  xdir_alb ,&! direct albedo for each band
39  xsca_alb ,&! diffuse albedo for each band
40  xemis ,&! emissivity
41  xtsrad ,&! radiative temperature
42  xtsun ,&! solar time (s from midnight)
43  xzs ,&! orography (m)
44  xzref ,&! height of T,q forcing (m)
45  xuref ,&! height of wind forcing (m)
46  xta ,&! air temperature forcing (K)
47  xqa ,&! air humidity forcing (kg/m3)
48  xsv ,&! scalar variables
49  xu ,&! zonal wind (m/s)
50  xv ,&! meridian wind (m/s)
51  xdir_sw ,&! direct solar radiation (on horizontal surf.)
52  xsca_sw ,&! diffuse solar radiation (on horizontal surf.)
53  xsw_bands ,&! mean wavelength of each shortwave band (m)
54  xzenith ,&! zenithal angle (radian from the vertical)
55  xzenith2 ,&! zenithal angle (radian from the vertical)
56  xazim ,&! azimuthal angle (radian from North, clockwise)
57  xlw ,&! longwave radiation (on horizontal surf.)
58  xps ,&! pressure at atmospheric model surface (Pa)
59  xpa ,&! pressure at forcing level (Pa)
60  xrhoa ,&! density at forcing level (kg/m3)
61  xco2 ,&! CO2 concentration in the air (kg/m3)
62  xsnow ,&! snow precipitation (kg/m2/s)
63  xrain ,&! liquid precipitation (kg/m2/s)
64  xsfth ,&! flux of heat (W/m2)
65  xsftq ,&! flux of water vapor (kg/m2/s)
66  xsfu ,&! zonal momentum flux (m/s)
67  xsfv ,&! meridian momentum flux (m/s)
68  xsfco2 ,&! flux of CO2 (kg/m2/s)
69  xsfts ,&! flux of scalar var. (kg/m2/s)
70  xpew_a_coef ,&! implicit coefficients
71  xpew_b_coef ,&! needed if HCOUPLING='I'
72  xpet_a_coef ,&
73  xpeq_a_coef ,&
74  xpet_b_coef ,&
75  xpeq_b_coef ,&
76  xtsurf ,&! effective temperature (K)
77  xz0 ,&! surface roughness length for momentum (m)
78  xz0h ,&! surface roughness length for heat (m)
79  xqsurf ! specific humidity at surface (kg/kg)
80 !
82 USE modd_csts, ONLY : xpi, xday, xrv, xrd, xg
84 USE modd_surf_par
91  cfilepgd_nc, ldef_nc=>ldef
92 USE modd_io_surf_ol, ONLY : xstart, xcount, xstride, lpartw, &
94  nstep_output, ldef_ol=>ldef
95 USE modd_write_bin, ONLY : nwrite
96 !
105 !
106 USE modd_surfex_omp, ONLY : nblock, nblocktot
107 !
111 !
114 !
115 USE modd_sfx_oasis, ONLY : loasis, xruntime
116 !
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_io_buff_clean
140 USE modi_init_surf_atm_n
141 USE modi_init_surf_landuse_n
142 USE modi_ol_time_interp_atm
143 USE modi_coupling_surf_atm_n
144 USE modi_add_forecast_to_date_surf
145 USE modi_write_surf_atm_n
146 USE modi_write_header_mnh
147 USE modi_flag_update
148 USE modi_flag_diag_update
149 USE modi_diag_surf_atm_n
150 USE modi_write_diag_surf_atm_n
151 USE modi_get_surf_var_n
153 USE modi_close_filein_ol
154 USE modi_close_fileout_ol
155 USE modi_init_output_ol_n
156 USE modi_init_output_nc_n
157 !
158 USE modi_write_header_fa
159 USE modi_abor1_sfx
160 !
161 USE modi_write_discharge_file
162 USE modi_write_budget_coupl_rout
163 USE modi_prep_restart_coupl_topd
164 !
165 USE modi_init_slope_param
166 USE modi_slope_radiative_effect
167 !
168 USE modi_sfx_oasis_read_nam
169 USE modi_sfx_oasis_init
170 USE modi_sfx_oasis_def_ol
171 USE modi_sfx_oasis_recv_ol
172 USE modi_sfx_oasis_send_ol
173 USE modi_sfx_oasis_end
174 !RJ: missing modi
175 USE modi_local_slope_param
176 !
177 #ifdef WXIOS
178 USE xios, ONLY : xios_context_finalize, xios_close_context_definition, xios_update_calendar
179 #endif
180 USE modi_sfx_xios_readnam_ol
181 USE modi_sfx_xios_setup_ol
182 !
183 USE mode_glt_dia_lu
184 !
185 #ifdef SFX_MPI
186 #ifdef SFX_MPL
188 #endif
189 #endif
190 USE yomhook ,ONLY : lhook, dr_hook
191 USE parkind1 ,ONLY : jprb
192 !
193 #ifdef AIX64
194 !$ USE OMP_LIB
195 #endif
196 !
197 IMPLICIT NONE
198 !
199 #ifdef SFX_MPI
200 include 'mpif.h'
201 #endif
202 !
203 #ifndef AIX64
204 !$ INCLUDE 'omp_lib.h'
205 #endif
206 !
207 !* 0. declarations of local variables
208 !
209  CHARACTER(LEN=3), PARAMETER :: YINIT = 'ALL'
210 !
211  CHARACTER(LEN=28) :: YLUOUT = 'LISTING_OFFLINE '
212 !
213 INTEGER :: IYEAR ! current year (UTC)
214 INTEGER :: IMONTH ! current month (UTC)
215 INTEGER :: IDAY ! current day (UTC)
216 INTEGER :: IYEAR2 ! current year at end of timestep(UTC)
217 INTEGER :: IMONTH2 ! current month at end of timestep(UTC)
218 INTEGER :: IDAY2 ! current day at end of timestep(UTC)
219 REAL :: ZTIME ! current time since start of the day (s)
220 REAL :: ZTIME2 ! current time since start of the day at end of timestep (s)
221 REAL :: ZTIMEC ! current duration since start of the run (s)
222 !
223 INTEGER :: IYEAR_OUT ! output year name
224 INTEGER :: IMONTH_OUT ! output month name
225 INTEGER :: IDAY_OUT ! output day name
226 REAL :: ZTIME_OUT ! output time since start of the run (s)
227 !
228 INTEGER, DIMENSION(11) :: IDATEF
229 !
230  CHARACTER(LEN=28), PARAMETER :: YATMFILE = ' '
231  CHARACTER(LEN=6), PARAMETER :: YATMFILETYPE = ' '
232  CHARACTER(LEN=2), PARAMETER :: YTEST = 'OK' ! must be equal to 'OK'
233 !
234 REAL, DIMENSION(:), POINTER :: ZLAT ! latitude (rad)
235 REAL, DIMENSION(:), POINTER :: ZLON ! longitude (rad)
236 REAL, DIMENSION(:), POINTER :: ZZS_FORC ! orography (m)
237 REAL, DIMENSION(:), POINTER :: ZZREF ! Forcing level for T
238 REAL, DIMENSION(:), POINTER :: ZUREF ! Forcing level for U
239 !
240 REAL :: ZTSTEP ! atmospheric time-step (s)
241 !
242 INTEGER :: INI ! grid dimension
243 INTEGER :: JLOOP ! loop counter
244 INTEGER :: IBANDS ! Number of radiative bands
245 INTEGER :: INB_STEP_ATM ! Number of atmospheric time-steps
246 INTEGER :: INB_ATM ! Number of Isba time-steps
247  ! within a forcing time-step
248 INTEGER :: ID_FORC ! indice of forcing in the file
249 INTEGER :: INB_LINES ! nb of lines to read in the forcing file
250 INTEGER :: IDMAX ! nb of lines to read in the forcing file at last
251 INTEGER :: JFORC_STEP ! atmospheric loop index
252 INTEGER :: JSURF_STEP ! isba loop index
253 INTEGER :: ICOUNT ! day counter
254 INTEGER :: ITIMESTARTINDEX
255 REAL :: ZDURATION, ZDURATION2 ! duration of run (s)
256 !
257 REAL, DIMENSION(:,:), ALLOCATABLE :: ZTA ! air temperature forcing (K)
258 REAL, DIMENSION(:,:), ALLOCATABLE :: ZQA ! air humidity forcing (kg/m3)
259 REAL, DIMENSION(:,:), ALLOCATABLE :: ZWIND ! wind speed (m/s)
260 REAL, DIMENSION(:,:), ALLOCATABLE :: ZSCA_SW ! diffuse solar radiation (on horizontal surf.)
261 REAL, DIMENSION(:,:), ALLOCATABLE :: ZDIR_SW ! direct solar radiation (on horizontal surf.)
262 REAL, DIMENSION(:,:), ALLOCATABLE :: ZLW ! longwave radiation (on horizontal surf.)
263 REAL, DIMENSION(:,:), ALLOCATABLE :: ZSNOW ! snow precipitation (kg/m2/s)
264 REAL, DIMENSION(:,:), ALLOCATABLE :: ZRAIN ! liquid precipitation (kg/m2/s)
265 REAL, DIMENSION(:,:), ALLOCATABLE :: ZPS ! pressure at forcing level (Pa)
266 REAL, DIMENSION(:,:), ALLOCATABLE :: ZCO2 ! CO2 concentration in the air (kg/m3)
267 REAL, DIMENSION(:,:), ALLOCATABLE :: ZDIR ! wind direction
268 INTEGER :: ILUOUT ! ascii output unit number
269 INTEGER :: ILUNAM ! namelist unit number
270 INTEGER :: IRET ! error return code
271 INTEGER :: INB
272 INTEGER :: INW, JNW
273  CHARACTER(LEN=14) :: YTAG
274 LOGICAL :: GFOUND ! return logical when reading namelist
275 LOGICAL :: GSHADOWS
276 REAL, DIMENSION(:), ALLOCATABLE :: ZSW ! total solar radiation (on horizontal surf.)
277 REAL, DIMENSION(:), ALLOCATABLE :: ZCOEF ! coefficient for solar radiation interpolation near sunset/sunrise
278 !
279 TYPE(date) :: TDATE_END
280 ! Flag diag :
281 !
282 INTEGER :: I2M, IBEQ, IDSTEQ
283 LOGICAL :: GFRAC, GDIAG_GRID, GSURF_BUDGET, GRAD_BUDGET, GCOEF, &
284  GSURF_VARS, GDIAG_OCEAN, GDIAG_SEAICE, GWATER_PROFILE, &
285  GINTERPOL_TS, GSURF_EVAP_BUDGET, GFLOOD, GPGD_ISBA, &
286  GCH_NO_FLUX_ISBA, GSURF_MISC_BUDGET_ISBA, GPGD_TEB, &
287  GSURF_MISC_BUDGET_TEB
288 !
289 ! Inquiry mode arrays:
290 !
291 REAL, DIMENSION(:), ALLOCATABLE :: ZSEA, ZWATER, ZNATURE, ZTOWN
292 REAL, DIMENSION(:), ALLOCATABLE :: ZSEA_FULL, ZWATER_FULL, ZNATURE_FULL, ZTOWN_FULL
293 REAL, DIMENSION(:), ALLOCATABLE :: ZT2M, ZQ2M
294 REAL, DIMENSION(:), ALLOCATABLE :: ZZ0, ZZ0H, ZQS
295 REAL, DIMENSION(:), ALLOCATABLE :: ZQS_SEA, ZQS_WATER, ZQS_NATURE, ZQS_TOWN
296 REAL, DIMENSION(:), ALLOCATABLE :: ZPSNG, ZPSNV
297 REAL, DIMENSION(:), ALLOCATABLE :: ZZ0EFF
298 REAL, DIMENSION(:), ALLOCATABLE :: ZZS
299 REAL, DIMENSION(:), ALLOCATABLE :: ZZ0_FULL, ZZ0EFF_FULL, ZZS_FULL
300 REAL, DIMENSION(:), ALLOCATABLE :: ZSUMZEN
301 INTEGER :: ISERIES, ISIZE
302 !
303 ! MPI variables
304 !
305  CHARACTER(LEN=100) :: YNAME
306  CHARACTER(LEN=10) :: YRANK
307 INTEGER :: ILEVEL, INFOMPI, J
308 REAL :: XTIME0, XTIME1, XTIME
309 !
310 ! SFX - OASIS coupling variables
311 !
312 LOGICAL :: GSAVHOOK
313 INTEGER :: IBLOCKTOT, IBLOCK
314 !
315 REAL(KIND=JPRB) :: ZHOOK_HANDLE
316 !
317 ! --------------------------------------------------------------------------------------
318 !
319 !* 0.1. MPI, OASIS, XIOS and dr_hook initializations
320 !
321 csoftware='OFFLINE'
322 !
323 infompi=1
324 !
325 gsavhook = lhook
326 lhook = .false.
327 ! There are issues with oasis if LHOOK=T during its init phase
328 #ifdef WXIOS
330 #else
331 lxios=.false.
332 #endif
333 lhook = gsavhook
334 !
335 !Must be call before DRHOOK !
337 #ifdef SFX_MPI
338 #ifdef SFX_MPL
339 IF (loasis.OR.lxios) THEN
340  lmplusercomm = .true.
342 ENDIF
343 #endif
344 #endif
345 !
346 #ifdef SFX_MPI
347 IF(.NOT.loasis.AND..NOT.lxios)THEN
348  CALL mpi_init_thread(mpi_thread_multiple,ilevel,infompi)
349  IF (infompi /= mpi_success) THEN
350  CALL abor1_sfx('OFFLINE: ERROR WHEN INITIALIZING MPI')
351  ENDIF
352  ncomm=mpi_comm_world
353 ENDIF
354  CALL mpi_comm_size(ncomm,nproc,infompi)
355  CALL mpi_comm_rank(ncomm,nrank,infompi)
356 #endif
357 !
358 IF (lhook) CALL dr_hook('OFFLINE',0,zhook_handle)
359 !
360 !RJ: init modd_surefx_omp
361 !$OMP PARALLEL
362 !$ NBLOCKTOT = OMP_GET_NUM_THREADS()
363 !$ NBLOCK = OMP_GET_THREAD_NUM()
364 !$OMP END PARALLEL
365 !
366 iblocktot = 1
367 iblock = 0
368 !
369  CALL prep_log_mpi
370 !
371  CALL wlog_mpi(' ')
372 !
373  CALL wlog_mpi('NBLOCKTOT ',klog=nblocktot)
374 !
375 #ifdef SFX_MPI
376 xtime0 = mpi_wtime()
377 #endif
378 !
379 !
380 !* 0.3. Open ascii file for writing
381 !
382 WRITE(yrank,fmt='(I10)') nrank
383 yname=trim(yluout)//adjustl(yrank)
384 !
385  cluout_lfi = adjustl(adjustr(yname)//'.txt')
386  cluout_nc = adjustl(adjustr(yname)//'.txt')
387 !
388  CALL get_luout('ASCII ',iluout)
389 OPEN(unit=iluout,file=adjustl(adjustr(yname)//'.txt'),form='FORMATTED',action='WRITE')
390 !
391 !
392 IF ( nrank==npio ) THEN
393  !
394 !RJ: be verbose just for openmp
395  IF(nblocktot==1) THEN
396 !$ WRITE(*,*) "CAUTION: DID YOU THINK TO SET OMP_NUM_THREADS=1?"
397 !$ WRITE(*,*) "PLEASE VERIFY OMP_NUM_THREADS IS INITIALIZED : TYPE ECHO $OMP_NUM_THREADS IN A TERMINAL"
398  !
399 !$ WRITE(ILUOUT,*) "CAUTION: DID YOU THINK TO SET OMP_NUM_THREADS=1?"
400 !$ WRITE(ILUOUT,*) "PLEASE VERIFY OMP_NUM_THREADS IS INITIALIZED : TYPE ECHO $OMP_NUM_THREADS IN A TERMINAL"
401  ENDIF
402  !
403 ENDIF
404 !
405 !* 0.4. Reads namelists
406 !
407  CALL open_namelist('ASCII ',ilunam,cnamelist)
408 !
409  CALL posnam(ilunam,'NAM_IO_OFFLINE',gfound,iluout)
410 IF (gfound) READ (unit=ilunam,nml=nam_io_offline)
411  CALL close_namelist('ASCII ',ilunam)
412 !
413 IF (nproc==1) THEN
414  xio_frac=1.
415 ELSE
416  xio_frac = max(min(xio_frac,1.),0.)
417 ENDIF
418 !
419  CALL test_nam_var_surf(iluout,'CSURF_FILETYPE',csurf_filetype,'ASCII ','LFI ','FA ','NC ')
420 #ifdef WXIOS
421  CALL test_nam_var_surf(iluout,'CTIMESERIES_FILETYPE',ctimeseries_filetype,'NETCDF','TEXTE ','BINARY',&
422  'ASCII ','LFI ','FA ',&
423  'NONE ','OFFLIN','NC '&
424  ,'XIOS ')
425 #else
426  CALL test_nam_var_surf(iluout,'CTIMESERIES_FILETYPE',ctimeseries_filetype,'NETCDF','TEXTE ','BINARY',&
427  'ASCII ','LFI ','FA ',&
428  'NONE ','OFFLIN','NC ')
429 #endif
430  CALL test_nam_var_surf(iluout,'CFORCING_FILETYPE',cforcing_filetype,'NETCDF','ASCII ','BINARY')
431 !
432 IF (nscal>59) CALL abor1_sfx("OFFLINE: NSCAL MUST BE LOWER THAN OR EQUAL TO 59")
433 !
434 !
435 IF (ctimeseries_filetype=='NETCDF') ctimeseries_filetype='OFFLIN'
436 !
437 IF ((trim(ctimeseries_filetype) /= 'XIOS') .AND. ladd_dim) THEN
438  CALL abor1_sfx('CANNOT YET SET LALLOW_ADD_DIM TO .TRUE. WITHOUT SETTING CTIMESERIES_FILETYPE to XIOS ')
439 ENDIF
440 !
441 !
442  cfilepgd = adjustl(adjustr(cpgdfile)//'.txt')
443  cfilein = adjustl(adjustr(cprepfile)//'.txt')
445 !
449 !
450  cfilepgd_fa = adjustl(adjustr(cpgdfile)//'.fa')
451  cfilein_fa = adjustl(adjustr(cprepfile)//'.fa')
453 !
454  cfilepgd_nc = adjustl(adjustr(cpgdfile)//'.nc')
455  cfilein_nc = adjustl(adjustr(cprepfile)//'.nc')
457 !
458 ! Allocations of Surfex Types
459  CALL surfex_alloc_list(1)
460  ysc => ysurf_list(1)
461 !
462 ! Reading all namelist (also assimilation)
463  CALL read_all_namelists(ysc, csurf_filetype,'ALL',.false.)
464 !
465 !
466 !* 0.5. Reads SFX - OASIS coupling namelists
467 !
469 !
470 !* 0.6 Assume FA filetype consistency
471 !
473 !
474 ! --------------------------------------------------------------------------------------
475 !
476 !* 1. Initializations
477 !
478 ! netcdf file handling
479 !
480 IF (nrank==npio) THEN
481  !
482  xstart = nundef
483  xstride = nundef
484  xcount = nundef
485  xstartw = 0
486  xcountw = 1
487  lpartw = .true.
488  !
489 ENDIF
490 !
491 #ifdef SFX_MPI
492 xtime = (mpi_wtime() - xtime0)
493 #endif
494  CALL wlog_mpi('READ NAMELISTS ',plog=xtime)
495 #ifdef SFX_MPI
496 xtime0 = mpi_wtime()
497 #endif
498 !
499 !
500 ! splitting of the grid
501 !
502 gshadows = lshadows_slope .OR. lshadows_other
503  CALL init_index_mpi(ysc%DTCO, ysc%U, ysc%UG, ysc%GCP, csurf_filetype, 'OFF', yalg_mpi, xio_frac, gshadows)
504 !
505  CALL wlog_mpi(' ')
506  CALL wlog_mpi('TIME_NPIO_READ init_index ',plog=xtime_npio_read)
507  CALL wlog_mpi('TIME_COMM_READ init_index ',plog=xtime_comm_read)
508 xtime_npio_read = 0.
509 xtime_comm_read = 0.
510 !
511 #ifdef SFX_MPI
512 xtime = (mpi_wtime() - xtime0)
513 #endif
514  CALL wlog_mpi(' ')
515  CALL wlog_mpi('INIT_INDEX_MPI ',plog=xtime)
516  CALL wlog_mpi(' ')
517 #ifdef SFX_MPI
518 xtime0 = mpi_wtime()
519 #endif
520 !
521 ! forcing file handling
522 !
523 IF (cforcing_filetype=='ASCII ' .OR. cforcing_filetype=='BINARY') CALL open_close_bin_asc_forc('CONF ',cforcing_filetype,'R')
524 IF (cforcing_filetype=='NETCDF') CALL open_filein_ol
525 !
526 ! configuration of run
527 !
528  CALL ol_read_atm_conf(ysc%DTCO, ysc%U, ysc%UG%G%CGRID, csurf_filetype, cforcing_filetype, &
529  ldelayedstart_nc, ndatestop, zduration, ztstep, ini, &
530  iyear, imonth, iday, ztime, zlat, zlon, zzs_forc, &
531  zzref, zuref, itimestartindex )
532 !
533 tdate_end%YEAR = iyear
534 tdate_end%MONTH = imonth
535 tdate_end%DAY = iday
536 zduration2 = zduration
537  CALL add_forecast_to_date_surf(tdate_end%YEAR, tdate_end%MONTH, tdate_end%DAY, zduration2)
538 !
539  CALL wlog_mpi(' ')
540  CALL wlog_mpi('TIME_NPIO_READ forc conf ',plog=xtime_npio_read)
541  CALL wlog_mpi('TIME_COMM_READ forc conf ',plog=xtime_comm_read)
542 xtime_npio_read = 0.
543 xtime_comm_read = 0.
544 !
545 #ifdef SFX_MPI
546 xtime = (mpi_wtime() - xtime0)
547 #endif
548  CALL wlog_mpi('OL_READ_ATM_CONF ',plog=xtime)
549  CALL wlog_mpi(' ')
550 #ifdef SFX_MPI
551 xtime0 = mpi_wtime()
552 #endif
553 !
554 !* time steps coherence check
555 !
556 IF ( (mod(xtstep_output,ztstep)*mod(ztstep,xtstep_output) /= 0) .OR. (mod(ztstep,xtstep_surf) /= 0) ) THEN
557  WRITE(iluout,*)' FORCING AND OUTPUT/SURFACE TIME STEP SHOULD BE MULTIPLE', &
558  nint(ztstep),nint(xtstep_output),nint(xtstep_surf)
559  CALL abor1_sfx('OFFLINE: FORCING AND OUTPUT/SURFACE TIME STEP SHOULD BE MULTIPLE')
560 ENDIF
561 !
562 IF ( ztime /= 0. .AND. mod(ztime,xtstep_surf) /= 0 ) THEN
563  WRITE(iluout,*)' INITIAL AND SURFACE TIME STEP SHOULD BE MULTIPLE', &
564  nint(ztime),nint(xtstep_surf)
565  CALL abor1_sfx('OFFLINE: INITIAL AND SURFACE TIME STEP SHOULD BE MULTIPLE')
566 ENDIF
567 !
568 IF(loasis.AND.zduration/=xruntime)THEN
569  WRITE(iluout,*)'Total simulated time given by Forcing field and OASIS namcouple are different'
570  WRITE(iluout,*)'From Forcing (s) : ',zduration, 'From OASIS (s) : ',xruntime
571  CALL abor1_sfx('OFFLINE: TOTAL SIMULATED TIME DIFFERENT BETWEEN FORCING AND OASIS')
572 ENDIF
573 !
574 inb_step_atm = int(zduration / ztstep)
575 inb_atm = int(ztstep / xtstep_surf)
576 nstep_output = int(zduration / xtstep_output)
577 !
578 xtopd_step = 0
579 nnb_topd_step = 0
580 ntopd_step = 0
581 IF ( lcoupl_topd ) THEN
582  !
584  nnb_topd_step = int( zduration / xtopd_step )
585  !
586  IF ( nnb_stp_restart==0 .AND. .NOT.lrestart ) nnb_stp_restart = -1
587  !
588  ntopd_step = 1
589  !
590 ENDIF
591 !
592 ! allocation of variables
593 !
594 ibands = 1
595 !
596  CALL ol_alloc_atm(ini,ibands,nscal)
597 !
598 xzs = zzs_forc
599 xzref = zzref
600 xuref = zuref
601 !
602 ! compare orography
603 !
605 !
606 ! miscellaneous initialization
607 !
608 icount = 0
609 ztimec = 0.
610 !
611  CALL sunpos(iyear, imonth, iday, ztime, zlon, zlat, xtsun, xzenith, xazim)
612 !
613 !number of lines read in forcing files
614 inb_lines=1
615 IF (nb_read_forc.EQ.1) THEN
616  inb_lines=inb_step_atm
617 ELSEIF (nb_read_forc.NE.0) THEN
618  !to be sure the number of readings will be NB_READ_FORC as a maximum
619  inb_lines=ceiling(1.*(inb_step_atm+1)/nb_read_forc)
620 ENDIF
621 !number of lines to be read effectively
622 idmax=inb_lines+1
623 !effective number of readings of the forcing files
624 nb_read_forc=ceiling(1.*(inb_step_atm+1)/inb_lines)
625 !
626 ! open Gelato specific diagnostic files (if requested by
627 ! Gelato wizzard user)
628 !
629 #if ! defined in_arpege
630  CALL opndia()
631 #endif
632 !
633 ! allocate local atmospheric variables
634 !
635 IF (.NOT.ALLOCATED(zta)) ALLOCATE(zta(ini,inb_lines+1))
636 IF (.NOT.ALLOCATED(zqa)) ALLOCATE(zqa(ini,inb_lines+1))
637 IF (.NOT.ALLOCATED(zwind)) ALLOCATE(zwind(ini,inb_lines+1))
638 IF (.NOT.ALLOCATED(zdir_sw))ALLOCATE(zdir_sw(ini,inb_lines+1))
639 IF (.NOT.ALLOCATED(zsca_sw))ALLOCATE(zsca_sw(ini,inb_lines+1))
640 IF (.NOT.ALLOCATED(zlw)) ALLOCATE(zlw(ini,inb_lines+1))
641 IF (.NOT.ALLOCATED(zsnow)) ALLOCATE(zsnow(ini,inb_lines+1))
642 IF (.NOT.ALLOCATED(zrain)) ALLOCATE(zrain(ini,inb_lines+1))
643 IF (.NOT.ALLOCATED(zps)) ALLOCATE(zps(ini,inb_lines+1))
644 IF (.NOT.ALLOCATED(zco2)) ALLOCATE(zco2(ini,inb_lines+1))
645 IF (.NOT.ALLOCATED(zdir)) ALLOCATE(zdir(ini,inb_lines+1))
646 IF (.NOT.ALLOCATED(zcoef)) ALLOCATE(zcoef(ini))
647 IF (.NOT.ALLOCATED(zsumzen))ALLOCATE(zsumzen(ini))
648 !
649 IF (.NOT.ALLOCATED(zsw))ALLOCATE(zsw(ini))
650 !
651 ! computes initial air co2 concentration and density
652 !
653 #ifdef SFX_MPI
654 xtime = (mpi_wtime() - xtime0)
655 #endif
656  CALL wlog_mpi('COMPARE_OROGRAPHY SUNPOS ',plog=xtime)
657 #ifdef SFX_MPI
658 xtime0 = mpi_wtime()
659 #endif
660 !
661 !* opens forcing files (if ASCII or BINARY)
662 !
663 IF (cforcing_filetype=='ASCII ' .OR. cforcing_filetype=='BINARY') &
665 !
666  CALL ol_read_atm(csurf_filetype, cforcing_filetype, itimestartindex,&
667  zta,zqa,zwind,zdir_sw,zsca_sw,zlw,zsnow,zrain,zps,&
668  zco2,zdir,llimit_qair )
669 !
670  CALL wlog_mpi(' ')
671  CALL wlog_mpi('TIME_NPIO_READ forc ',plog=xtime_npio_read)
672  CALL wlog_mpi('TIME_COMM_READ forc ',plog=xtime_comm_read)
673 xtime_npio_read = 0.
674 xtime_comm_read = 0.
675 !
676 #ifdef SFX_MPI
677 xtime = (mpi_wtime() - xtime0)
678 #endif
679  CALL wlog_mpi(' ')
680  CALL wlog_mpi('OL_READ_ATM0 ',plog=xtime)
681  CALL wlog_mpi(' ')
682 #ifdef SFX_MPI
683 xtime0 = mpi_wtime()
684 #endif
685 !
686 xco2(:) = zco2(:,1)
687 xrhoa(:) = zps(:,1) / (xrd * zta(:,1) * ( 1.+((xrv/xrd)-1.)*zqa(:,1) ) + xg * xzref )
688 !
689 ! surface Initialisation
690 !
691 #ifdef SFX_MPI
692 xtime = (mpi_wtime() - xtime0)
693 #endif
694  CALL wlog_mpi('CO2 RHOA ',plog=xtime)
695 !
696  CALL io_buff_clean
697 !
698  !CALL SURFEX_DEALLO_LIST
699  !CALL SURFEX_ALLOC_LIST(IBLOCKTOT)
700 !
701 #ifdef SFX_MPI
702 xtime0 = mpi_wtime()
703 #endif
704 !
705  CALL goto_model(1)
706 !
707  CALL init_surf_atm_n(ysc, csurf_filetype, yinit, lland_use, ini, nscal, ibands, &
708  csv,xco2(:),xrhoa(:), xzenith(:),xazim(:),xsw_bands, &
709  xdir_alb(:,:), xsca_alb(:,:), xemis(:), xtsrad(:), &
710  xtsurf(:), iyear, imonth, iday, ztime, tdate_end, &
711  yatmfile, yatmfiletype, ytest )
712 !
713 ! initialization routines to compute shadows
714 IF (gshadows) THEN
715  IF (iblock==0) THEN
716  CALL init_slope_param(ysc%UG%G, ysc%UG%XGRID_FULL_PAR,zzs_forc,ini,zlat)
717  END IF
718  CALL local_slope_param(1,ini)
719 END IF
720 !
721 #ifdef SFX_MPI
722 xtime = (mpi_wtime() - xtime0)
723 #endif
724  CALL wlog_mpi(' ')
725  CALL wlog_mpi('INIT_SURF_ATM ',plog=xtime)
726  CALL wlog_mpi(' ')
727 !
728  CALL wlog_mpi('TIME_NPIO_READ init ',plog=xtime_npio_read)
729  CALL wlog_mpi('TIME_COMM_READ init ',plog=xtime_comm_read)
730  CALL wlog_mpi(' ')
731 !
732 xtime_npio_read = 0.
733 xtime_comm_read = 0.
734 !
735 ! Land use or/and vegetation dynamic
736 !
737  CALL init_surf_landuse_n(ysc%DTCO, ysc%DUO%LREAD_BUDGETC, ysc%U, ysc%UG, &
738  ysc%IM, ysc%SV, ysc%SLT, ysc%NDST, csurf_filetype,&
739  yinit, lland_use, ini, nscal, ibands, csv, &
740  xco2, xrhoa, xzenith, xazim, xsw_bands, xdir_alb, &
741  xsca_alb, xemis, xtsrad, xtsurf, iyear, imonth, &
742  iday, ztime, yatmfile, yatmfiletype, ytest )
743 !
744 #ifdef SFX_MPI
745 xtime0 = mpi_wtime()
746 #endif
747 !
748  CALL init_crodebug(ysc%IM%NPE%AL(1)%TSNOW%SCHEME)
749 !
750 ! * SURFEX - OASIS grid, partitions and local field definitions
751 !
752 IF(loasis)THEN
754 ENDIF
755 !
756 ! --------------------------------------------------------------------------------------
757 !
758  CALL sfx_xios_setup_ol(ysc,iluout,iyear,imonth,iday,ztime,xtstep_output)
759 !
760 nwrite = 0
761 !
762 #ifdef SFX_MPI
763 xtime = (mpi_wtime() - xtime0)
764 #endif
765  CALL wlog_mpi('INIT FINISHED ',plog=xtime)
766 #ifdef SFX_MPI
767 xtime0 = mpi_wtime()
768 #endif
769 !* 2. Temporal loops
770 !
771 xtime_calc(:) = 0.
772 xtime_write(:) = 0.
773 !
774 lfirst_write = .true.
775 !
776 ncpt_write = 0
777 !
778 DO jforc_step=1,inb_step_atm
779  !
780 #ifdef SFX_MPI
781  xtime1 = mpi_wtime()
782 #endif
783  ! read Forcing
784  !
785  !indice of forcing line in forcing arrays
786  id_forc=jforc_step-int(jforc_step/inb_lines)*inb_lines
787  IF (id_forc==0) id_forc=inb_lines
788  !new forcings to read
789  IF (id_forc==1 .AND. jforc_step.NE.1) THEN
790  !if last part of forcing, the last point has to be adjusted on the end of
791  !files
792  IF (jforc_step/inb_lines==nb_read_forc-1) THEN
793  idmax=inb_step_atm-jforc_step+1+1
794  !for ascii and binary forcing files
795  zta(:,idmax) = zta(:,SIZE(zta,2))
796  zqa(:,idmax) = zqa(:,SIZE(zta,2))
797  zwind(:,idmax) = zwind(:,SIZE(zta,2))
798  zdir_sw(:,idmax) = zdir_sw(:,SIZE(zta,2))
799  zsca_sw(:,idmax) = zsca_sw(:,SIZE(zta,2))
800  zlw(:,idmax) = zlw(:,SIZE(zta,2))
801  zsnow(:,idmax) = zsnow(:,SIZE(zta,2))
802  zrain(:,idmax) = zrain(:,SIZE(zta,2))
803  zps(:,idmax) = zps(:,SIZE(zta,2))
804  zco2(:,idmax) = zco2(:,SIZE(zta,2))
805  zdir(:,idmax) = zdir(:,SIZE(zta,2))
806  ENDIF
807  CALL ol_read_atm(csurf_filetype, cforcing_filetype, itimestartindex+jforc_step-1, &
808  zta(:,1:idmax),zqa(:,1:idmax),zwind(:,1:idmax), &
809  zdir_sw(:,1:idmax),zsca_sw(:,1:idmax),zlw(:,1:idmax), &
810  zsnow(:,1:idmax),zrain(:,1:idmax),zps(:,1:idmax), &
811  zco2(:,1:idmax),zdir(:,1:idmax),llimit_qair )
812  ENDIF
813 
814 #ifdef SFX_MPI
815  xtime_calc(1) = xtime_calc(1) + (mpi_wtime() - xtime1)
816  xtime1 = mpi_wtime()
817 #endif
818  !
819  !COMPUTE SUM ZENITH angle between 2 timestepA
820  zsumzen(:)=0.0
821  DO jsurf_step = 1,inb_atm
822  iday2 = iday
823  ztime2 = ztime + (jsurf_step-1.)*xtstep_surf
824  IF (ztime2>86400.) THEN
825  ztime2 = ztime2-86400
826  iday2 = iday+1
827  ENDIF
828  CALL sunpos(iyear, imonth, iday2, ztime+(jsurf_step-1.)*xtstep_surf, &
829  zlon, zlat, xtsun, xzenith, xazim)
830  !
831  zsumzen(:)= zsumzen(:) + max(cos(xzenith(:)+0.1),0.)/(inb_atm*1.0)
832  !
833  ENDDO
834  WHERE ( zsumzen<0.01 ) zsumzen = 0.0
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  !
844  CALL sunpos(iyear, imonth, iday, ztime, zlon, zlat, xtsun, xzenith, xazim)
845  iyear2 = iyear
846  imonth2= imonth
847  iday2 = iday
848  ztime2 = ztime+xtstep_surf
849  CALL add_forecast_to_date_surf(iyear2, imonth2, iday2, ztime2)
850  CALL sunpos(iyear2, imonth2, iday2, ztime2, zlon, zlat, xtsun, xzenith2, xazim)
851  !
852 #ifdef SFX_MPI
853  xtime_calc(2) = xtime_calc(2) + (mpi_wtime() - xtime1)
854  xtime1 = mpi_wtime()
855 #endif
856  !interpolation between beginning and end of current forcing time step
857  CALL ol_time_interp_atm(jsurf_step,inb_atm, &
858  zta(:,id_forc),zta(:,id_forc+1), &
859  zqa(:,id_forc),zqa(:,id_forc+1), &
860  zwind(:,id_forc),zwind(:,id_forc+1), &
861  zdir_sw(:,id_forc),zdir_sw(:,id_forc+1), &
862  zsca_sw(:,id_forc),zsca_sw(:,id_forc+1), &
863  zlw(:,id_forc),zlw(:,id_forc+1), &
864  zsnow(:,id_forc+1),zrain(:,id_forc+1), &
865  zps(:,id_forc),zps(:,id_forc+1), &
866  zco2(:,id_forc),zco2(:,id_forc+1), &
867  zdir(:,id_forc),zdir(:,id_forc+1), &
868  xzenith+0.1,zsumzen )
869 #ifdef SFX_MPI
870  xtime_calc(3) = xtime_calc(3) + (mpi_wtime() - xtime1)
871  xtime1 = mpi_wtime()
872 #endif
873  !
874  IF(ladapt_sw)THEN
875  !
876  ! coherence between solar zenithal angle and radiation
877  ! when solar beam close to horizontal -> reduction of direct radiation to
878  ! the benefit of scattered radiation
879  ! when pi/2 - 0.1 < ZENITH < pi/2 - 0.05 => weight of direct to scattered radiation decreases linearly with zenith
880  ! when pi/2 - 0.05 < ZENITH => all the direct radiation is converted to scattered radiation
881  ! coherence between solar zenithal angle and radiation
882  !
883  zcoef(:) = (xpi/2. - xzenith(:) - 0.05) / 0.05
884  zcoef(:) = max(min(zcoef,1.),0.)
885  DO jloop=1,SIZE(xdir_sw,2)
886  xsca_sw(:,jloop) = xsca_sw(:,jloop) + xdir_sw(:,jloop) * (1 - zcoef)
887  xdir_sw(:,jloop) = xdir_sw(:,jloop) * zcoef(:)
888  ENDDO
889  !
890  ELSE
891  !
892  zsw(:) = 0.
893  DO jloop=1,SIZE(xdir_sw,2)
894  zsw(:) = zsw(:) + xdir_sw(:,jloop) + xsca_sw(:,jloop)
895  END DO
896  WHERE (zsw(:)>0.)
897  xzenith = min(xzenith ,xpi/2.-0.01)
898  xzenith2 = min(xzenith2,xpi/2.-0.01)
899  ELSEWHERE
900  xzenith = max(xzenith ,xpi/2.)
901  xzenith2 = max(xzenith2,xpi/2.)
902  END WHERE
903  !
904  ENDIF
905  !
906  ! updates time
907  ztimec= ztimec+xtstep_surf
908  IF (lcoupl_topd) ltopd_step = ( mod((((jforc_step-1)*inb_atm)+jsurf_step),nnb_topd) == 0 )
909  !
910  ! run Surface
911  !
912 #ifdef SFX_MPI
913  xtime_calc(4) = xtime_calc(4) + (mpi_wtime() - xtime1)
914 #endif
915  !
916  CALL io_buff_clean
917  !
918  IF(loasis)THEN
919  ! Receive fields to other models proc by proc
920  CALL sfx_oasis_recv_ol(ysc%FM%F, ysc%IM, ysc%SM%S, ysc%U, ysc%WM%W, &
921  csurf_filetype, ini, ibands, ztimec, xtstep_surf, xzenith, &
922  xsw_bands, xtsrad, xdir_alb, xsca_alb, xemis, xtsurf )
923  ENDIF
924  !
925 #ifdef SFX_MPI
926  xtime1 = mpi_wtime()
927 #endif
928  !
929  IF(gshadows) THEN
930  CALL slope_radiative_effect(xtstep_surf, xzenith, xazim, xps, xta, xrain, xdir_sw, xlw, &
933  END IF
934  !
935  CALL coupling_surf_atm_n(ysc, csurf_filetype, 'E', ztimec, xtstep_surf, iyear, imonth, iday, ztime, &
936  ini, nscal, ibands, xtsun, xzenith, xzenith2, xazim, xzref, xuref, &
937  xzs, xu, xv, xqa, xta, xrhoa, xsv, xco2, csv, xrain, xsnow, xlw, xdir_sw, &
938  xsca_sw, xsw_bands, xps, xpa, xsftq, xsfth, xsfts, xsfco2, xsfu, xsfv, &
939  xtsrad, xdir_alb, xsca_alb, xemis, xtsurf, xz0, xz0h, xqsurf, xpew_a_coef, &
940  xpew_b_coef,xpet_a_coef,xpeq_a_coef,xpet_b_coef,xpeq_b_coef, ytest )
941  !
942 #ifdef SFX_MPI
943  xtime_calc(5) = xtime_calc(5) + (mpi_wtime() - xtime1)
944 #endif
945  !
946 #ifdef SFX_MPI
947  xtime1 = mpi_wtime()
948 #endif
949  !
950  IF(loasis)THEN
951  ! Send fields to other models proc by proc
952  CALL sfx_oasis_send_ol(ysc%FM%F, ysc%IM, ysc%SM%S, ysc%U, ysc%WM%W, csurf_filetype,ini,ztimec,xtstep_surf)
953  ENDIF
954  !
955  ztime = ztime + xtstep_surf
956  CALL add_forecast_to_date_surf(iyear, imonth, iday, ztime)
957 #ifdef SFX_MPI
958  xtime_calc(6) = xtime_calc(6) + (mpi_wtime() - xtime1)
959  !
960  xtime1 = mpi_wtime()
961 #endif
962  ! ecrit Surface
963  !
964  IF ( lcoupl_topd .AND. ltopd_step ) THEN
965  !
966  IF (.NOT.ALLOCATED(nyear)) ALLOCATE(nyear(nnb_topd_step))
967  IF (.NOT.ALLOCATED(nmonth)) ALLOCATE(nmonth(nnb_topd_step))
968  IF (.NOT.ALLOCATED(nday)) ALLOCATE(nday(nnb_topd_step))
969  IF (.NOT.ALLOCATED(nh)) ALLOCATE(nh(nnb_topd_step))
970  IF (.NOT.ALLOCATED(nm)) ALLOCATE(nm(nnb_topd_step))
971  !
972  nyear(ntopd_step) = iyear
973  nmonth(ntopd_step) = imonth
974  nday(ntopd_step) = iday
975  nh(ntopd_step) = int(ztime/3600.)
976  nm(ntopd_step) = int((ztime-nh(ntopd_step)*3600.)/60.)
977  !
978  IF ( nm(ntopd_step)==60 ) THEN
979  !
980  nm(ntopd_step) = 0
981  nh(ntopd_step) = nh(ntopd_step)+1
982  !
983  ENDIF
984  !
985  IF ( nh(ntopd_step)==24 ) THEN
986  !
987  nh(ntopd_step) = 0
989  !
990  !!AJOUT BEC
991  SELECT CASE (nmonth(ntopd_step))
992  CASE(4,6,9,11)
993  IF ( nday(ntopd_step)==31 ) THEN
995  nday(ntopd_step) = 1
996  ENDIF
997  CASE(1,3,5,7:8,10)
998  IF ( nday(ntopd_step)==32 ) THEN
1000  nday(ntopd_step) = 1
1001  ENDIF
1002  CASE(12)
1003  IF ( nday(ntopd_step)==32 ) THEN
1005  nmonth(ntopd_step) = 1
1006  nday(ntopd_step) = 1
1007  ENDIF
1008  CASE(2)
1009  IF( mod(nyear(ntopd_step),4)==0 .AND. mod(nyear(ntopd_step),100)/=0 .OR. mod(nyear(ntopd_step),400)==0 ) THEN
1010  IF (nday(ntopd_step)==30) THEN
1012  nday(ntopd_step) = 1
1013  ENDIF
1014  ELSE
1015  IF (nday(ntopd_step)==29) THEN
1017  nday(ntopd_step) = 1
1018  ENDIF
1019  ENDIF
1020  END SELECT
1021  !
1022  ENDIF
1023  !
1024  ! * 2. Stocking date of each time step
1025  !
1026  ntopd_step = ntopd_step + 1
1027  !
1028  ENDIF
1029  !
1030  IF (mod(ztimec,xtstep_output) == 0. .AND. ctimeseries_filetype/='NONE ') THEN
1031  !
1032  IF (nrank==npio) THEN
1033  !
1034  !* name of the file
1035  IF (ctimeseries_filetype=="ASCII " .OR. &
1036  ctimeseries_filetype=="LFI " .OR. &
1037  ctimeseries_filetype=="FA " .OR. &
1038  ctimeseries_filetype=="NC " ) THEN
1039  !
1040  !
1041  ztime_out = ztime
1042  iday_out = iday
1043  imonth_out = imonth
1044  iyear_out = iyear
1045  !
1046  IF(lout_timename)THEN
1047  ! if true, change the name of output file at the end of a day
1048  ! (ex: 19860502_00h00 -> 19860501_24h00)
1049  IF(ztime==0.0)THEN
1050  ztime_out = 86400.
1051  iday_out = iday-1
1052  IF(iday_out==0)THEN
1053  imonth_out = imonth - 1
1054  IF(imonth_out==0)THEN
1055  imonth_out=12
1056  iyear_out = iyear - 1
1057  ENDIF
1058  SELECT CASE (imonth_out)
1059  CASE(4,6,9,11)
1060  iday_out=30
1061  CASE(1,3,5,7:8,10,12)
1062  iday_out=31
1063  CASE(2)
1064  IF( ((mod(iyear_out,4)==0).AND.(mod(iyear_out,100)/=0)) .OR. (mod(iyear_out,400)==0))THEN
1065  iday_out=29
1066  ELSE
1067  iday_out=28
1068  ENDIF
1069  END SELECT
1070  ENDIF
1071  ENDIF
1072  !
1073  ENDIF
1074  !
1075  WRITE(ytag,fmt='(I4.4,I2.2,I2.2,A1,I2.2,A1,I2.2)') iyear_out,imonth_out,iday_out,&
1076  '_',int(ztime_out/3600.),'h',nint(ztime_out)/60-60*int(ztime_out/3600.)
1077  cfileout = adjustl(adjustr(csurffile)//'.'//ytag//'.txt')
1078  cfileout_lfi= adjustl(adjustr(csurffile)//'.'//ytag)
1079  cfileout_fa = adjustl(adjustr(csurffile)//'.'//ytag//'.fa')
1080  cfileout_nc = adjustl(adjustr(csurffile)//'.'//ytag//'.nc')
1081  !
1082  IF (ctimeseries_filetype=='FA ') THEN
1083 #ifdef SFX_FA
1085  idatef(1)= iyear!_OUT
1086  idatef(2)= imonth!_OUT
1087  idatef(3)= iday!_OUT
1088  !ZTIME instead of ZTIME_OUT (FA XRD39 do not like 24h)
1089  idatef(4)= floor(ztime/3600.)
1090  idatef(5)= floor(ztime/60.) - idatef(4) * 60
1091  idatef(6)= nint(ztime) - idatef(4) * 3600 - idatef(5) * 60
1092  idatef(7:11) = 0
1093  nunit_fa = 19
1094  IF (csurf_filetype/='FA ') THEN
1095  CALL write_header_fa(ysc%GCP, ysc%UG%G%CGRID, ysc%UG%XGRID_FULL_PAR, csurf_filetype,'ALL')
1096  ELSE
1097  CALL faitou(iret,nunit_fa,.true.,cfileout_fa,'UNKNOWN',.true.,.false.,iverbfa,0,inb,cdnomc)
1098  ENDIF
1099  CALL fandar(iret,nunit_fa,idatef)
1100 #endif
1101  END IF
1102  !
1103  END IF
1104  !
1105  xstartw = xstartw + 1
1106  nwrite = nwrite + 1
1107  ltime_written=.false.
1108  !
1109  ENDIF
1110  !
1111 #ifdef SFX_MPI
1112  xtime_write(1) = xtime_write(1) + (mpi_wtime() - xtime1)
1113 #endif
1114  !
1115  inw = 1
1116  !
1117  IF ( lxios .AND. .NOT. lxios_def_closed ) inw = 2
1118  !
1119  ldef_nc = .false.
1120  IF (ctimeseries_filetype=="NC ") THEN
1121  ldef_nc = .true.
1122  inw = 2
1123  CALL init_output_nc_n (ysc%TM%BDD, ysc%CHE, ysc%CHN, ysc%CHU, ysc%SM%DTS, &
1124  ysc%TM%DTT, ysc%DTZ, ysc%IM, ysc%UG, ysc%U, ysc%DUO%CSELECT)
1125  ENDIF
1126  !
1127  ldef_ol = .false.
1128  IF (ctimeseries_filetype=="OFFLIN".AND.lfirst_write) THEN
1129  ldef_ol = .true.
1130  inw = 2
1131  IF (ctimeseries_filetype=="OFFLIN") CALL init_output_ol_n (ysc)
1132  ENDIF
1133  !
1134  idx_w = 0
1135  !
1136  DO jnw = 1,inw
1137  !
1138  CALL io_buff_clean
1139  !
1140 #ifdef SFX_MPI
1141  xtime1 = mpi_wtime()
1142 #endif
1143  IF (lxios) THEN
1144 #ifdef WXIOS
1145  ntimestep=int(ztimec/xtstep_output + 1.)
1146 #endif
1147  ENDIF
1149 #ifdef SFX_MPI
1150  xtime_write(2) = xtime_write(2) + (mpi_wtime() - xtime1)
1151  xtime1 = mpi_wtime()
1152 #endif
1154 #ifdef SFX_MPI
1155  xtime_write(3) = xtime_write(3) + (mpi_wtime() - xtime1)
1156  xtime1 = mpi_wtime()
1157 #endif
1159  !
1160  IF (lxios) THEN
1161 #ifdef WXIOS
1162  IF (.NOT. lxios_def_closed) THEN
1163  CALL xios_close_context_definition()
1164  lxios_def_closed=.true.
1165  ENDIF
1166  CALL xios_update_calendar(ntimestep)
1167 #endif
1168  ENDIF
1169  !
1170 #ifdef SFX_MPI
1171  xtime_write(4) = xtime_write(4) + (mpi_wtime() - xtime1)
1172 #endif
1173  !
1174  ldef_nc = .false.
1175  ldef_ol = .false.
1176  !
1177  ncpt_write = 0
1178  !
1179  lfirst_write = .false.
1180  !
1181  ENDDO
1182  !
1183  IF (lcoupl_topd .AND. ntopd_step > nnb_topd_step) THEN
1184  !
1185  ! Writing of file resulting of coupling with TOPMODEL or routing ****
1186  CALL write_discharge_file(csurf_filetype,'q_total.txt','FORMATTED',&
1188  CALL write_discharge_file(csurf_filetype,'q_runoff.txt','FORMATTED',&
1190  CALL write_discharge_file(csurf_filetype,'q_drainage.txt','FORMATTED',&
1192  ! Writing of budget files
1194  !
1195  ENDIF
1196  !
1197 #ifdef SFX_MPI
1198  xtime1 = mpi_wtime()
1199 #endif
1200  !
1201  IF (nrank==npio) THEN
1202  IF (ctimeseries_filetype=='FA ') THEN
1203 #ifdef SFX_FA
1204  CALL fairme(iret,nunit_fa,'UNKNOWN')
1205 #endif
1206  END IF
1207  !* add informations in the file
1208  IF (ctimeseries_filetype=='LFI ' .AND. lmnh_compatible) CALL write_header_mnh
1209  ENDIF
1210 #ifdef SFX_MPI
1211  xtime_write(5) = xtime_write(5) + (mpi_wtime() - xtime1)
1212 #endif
1213  !
1214  ENDIF
1215  !
1216  END DO
1217  !
1218  IF (nrank==npio) THEN
1219  IF (lprint) THEN
1220  IF (mod(ztimec,xday) == 0.) THEN
1221  icount = icount + 1
1222  CALL wlog_mpi('SFX DAY :',klog=icount,klog2=int(zduration/xday))
1223  WRITE(*,'(A10,I5,A2,I5)')'SFX DAY :',icount,' /',int(zduration/xday)
1224  ENDIF
1225  ENDIF
1226  ENDIF
1227  !
1228 END DO
1229 !
1230  CALL wlog_mpi(' ')
1231  CALL wlog_mpi('OL_READ_ATM ',plog=xtime_calc(1))
1232  CALL wlog_mpi('SUNPOS ',plog=xtime_calc(2))
1233  CALL wlog_mpi('OL_TIME_INTERP_ATM ',plog=xtime_calc(3))
1234  CALL wlog_mpi('')
1235  CALL wlog_mpi('ZENITH ',plog=xtime_calc(4))
1236  CALL wlog_mpi('')
1237  CALL wlog_mpi('COUPLING_SURF_ATM ',plog=xtime_calc(5))
1238  CALL wlog_mpi('')
1239  CALL wlog_mpi('ADD_FORECAST_TO_DATE_SURF ',plog=xtime_calc(6))
1240  CALL wlog_mpi('DEF_DATE ',plog=xtime_write(1))
1241  CALL wlog_mpi('')
1242  CALL wlog_mpi('WRITE_SURF_ATM ',plog=xtime_write(2))
1243  CALL wlog_mpi('DIAG_SURF_ATM ',plog=xtime_write(3))
1244  CALL wlog_mpi('WRITE_DIAG_SURF_ATM ',plog=xtime_write(4))
1245  CALL wlog_mpi('')
1246  CALL wlog_mpi('CLOSE FILES ',plog=xtime_write(5))
1247  CALL wlog_mpi('')
1248 !
1249 IF (cforcing_filetype=='ASCII ' .OR. cforcing_filetype=='BINARY') &
1250  CALL open_close_bin_asc_forc('CLOSE',cforcing_filetype,'R')
1251 !
1252 IF (cforcing_filetype=='NETCDF') CALL close_filein_ol
1253 IF (ctimeseries_filetype=='OFFLIN') CALL close_fileout_ol
1254 !
1255 ! --------------------------------------------------------------------------------------
1256 !
1257 !* 3. write restart file
1258 ! ------------------
1259 !
1260 IF ( lrestart ) THEN
1261  !
1262  lfirst_write = .true.
1263  !
1264  IF (nrank==npio) THEN
1265  !* name of the file
1266  cfileout = adjustl(adjustr(csurffile)//'.txt')
1268  cfileout_fa = adjustl(adjustr(csurffile)//'.fa')
1269  cfileout_nc = adjustl(adjustr(csurffile)//'.nc')
1270 
1271  !* opens the file
1272  IF (csurf_filetype=='FA ') THEN
1273 #ifdef SFX_FA
1274  lfanocompact = .true.
1275  idatef(1)= iyear
1276  idatef(2)= imonth
1277  idatef(3)= iday
1278  idatef(4)= floor(ztime/3600.)
1279  idatef(5)= floor(ztime/60.) - idatef(4) * 60
1280  idatef(6)= nint(ztime) - idatef(4) * 3600 - idatef(5) * 60
1281  idatef(7:11) = 0
1282  nunit_fa = 19
1283  CALL faitou(iret,nunit_fa,.true.,cfileout_fa,'UNKNOWN',.true.,.false.,iverbfa,0,inb,cdnomc)
1284  CALL fandar(iret,nunit_fa,idatef)
1285 #endif
1286  END IF
1287  !
1288  ENDIF
1289  !
1290  inw = 1
1291  IF (csurf_filetype=="NC ") inw = 2
1292  !
1293  ldef_nc = .true.
1294  ldef_ol = .true.
1295  !
1296  IF (ASSOCIATED(ysc%DUO%CSELECT)) DEALLOCATE(ysc%DUO%CSELECT)
1297  ALLOCATE(ysc%DUO%CSELECT(0))
1298  !
1299  IF (csurf_filetype=="NC ") THEN
1300  CALL init_output_nc_n (ysc%TM%BDD, ysc%CHE, ysc%CHN, ysc%CHU, ysc%SM%DTS, ysc%TM%DTT, &
1301  ysc%DTZ, ysc%IM, ysc%UG, ysc%U, ysc%DUO%CSELECT)
1302  ENDIF
1303  !
1304  DO jnw = 1,inw
1305  !
1306  CALL io_buff_clean
1307  !
1308  CALL flag_update(ysc%IM%ID%O, ysc%DUO,.false.,.true.,.false.,.false.)
1309  !
1310  IF (lrestart_2m) THEN
1311  i2m = 1
1312  gpgd_isba = .true.
1313  ELSE
1314  i2m = 0
1315  gpgd_isba = .false.
1316  ENDIF
1317  gfrac = .true.
1318  gdiag_grid = .true.
1319  gsurf_budget = .false.
1320  grad_budget = .false.
1321  gcoef = .false.
1322  gsurf_vars = .false.
1323  ibeq = 0
1324  idsteq = 0
1325  gdiag_ocean = .false.
1326  gdiag_seaice = .false.
1327  gwater_profile = .false.
1328  gsurf_evap_budget = .false.
1329  gflood = .false.
1330  gch_no_flux_isba = .false.
1331  gsurf_misc_budget_isba = .false.
1332  gpgd_teb = .false.
1333  gsurf_misc_budget_teb = .false.
1334  !
1335  CALL flag_diag_update(ysc%FM, ysc%IM, ysc%SM, ysc%TM, ysc%WM, ysc%DUO, ysc%U, ysc%SV, &
1336  gfrac, gdiag_grid, i2m, gsurf_budget, grad_budget, gcoef, &
1337  gsurf_vars, ibeq, idsteq, gdiag_ocean, gdiag_seaice, &
1338  gwater_profile, gsurf_evap_budget, gflood, gpgd_isba, &
1339  gch_no_flux_isba, gsurf_misc_budget_isba, gpgd_teb, &
1340  gsurf_misc_budget_teb )
1341  !
1342  ysc%DUO%LSNOWDIMNC = .false.
1343  !
1344  !* writes into the file
1346  IF(csurf_filetype/='FA ' .OR. lrestart_2m) THEN
1348  ENDIF
1349  !
1350  ldef_nc = .false.
1351  ldef_ol = .false.
1352  !
1353  ncpt_write = 0
1354  !
1355  lfirst_write = .false.
1356  !
1357  ENDDO
1358  !
1359  !* closes the file
1360  IF (nrank==0 ) THEN
1361  IF (csurf_filetype=='FA ') THEN
1362 #ifdef SFX_FA
1363  CALL fairme(iret,nunit_fa,'UNKNOWN')
1364 #endif
1365  END IF
1366  !* add informations in the file
1367  IF (csurf_filetype=='LFI ' .AND. lmnh_compatible) CALL write_header_mnh
1368  !
1369  ENDIF
1370  !
1371  IF (lcoupl_topd .AND. ntopd_step > nnb_topd_step) &
1373  !
1374 END IF
1375 !
1376 ! --------------------------------------------------------------------------------------
1377 !
1378 !* 4. inquiry mode
1379 ! ------------
1380 !
1381 IF ( linquire ) THEN
1382  !
1383  ALLOCATE( zsea( ini ) )
1384  ALLOCATE( zwater( ini ) )
1385  ALLOCATE( znature( ini ) )
1386  ALLOCATE( ztown( ini ) )
1387  ALLOCATE( zt2m( ini ) )
1388  ALLOCATE( zq2m( ini ) )
1389  ALLOCATE( zz0( ini ) )
1390  ALLOCATE( zz0h( ini ) )
1391  ALLOCATE( zqs_sea( ini ) )
1392  ALLOCATE( zqs_water( ini ) )
1393  ALLOCATE( zqs_nature( ini ) )
1394  ALLOCATE( zqs_town( ini ) )
1395  ALLOCATE( zqs( ini ) )
1396  ALLOCATE( zpsng( ini ) )
1397  ALLOCATE( zpsnv( ini ) )
1398  ALLOCATE( zz0eff( ini ) )
1399  ALLOCATE( zzs( ini ) )
1400  !
1401  iseries = 0
1402  CALL get_surf_var_n(ysc%FM, ysc%IM, ysc%SM, ysc%TM, ysc%WM, ysc%DUO, ysc%DU, ysc%UG, ysc%U, ysc%USS, &
1403  csurf_filetype,ini,iseries,psea=zsea,pwater=zwater,pnature=znature,ptown=ztown, &
1404  pt2m=zt2m,pq2m=zq2m,pqs=zqs,pz0=zz0,pz0h=zz0h,pz0eff=zz0eff,pqs_sea=zqs_sea, &
1405  pqs_water=zqs_water,pqs_nature=zqs_nature,pqs_town=zqs_town, &
1406  ppsng=zpsng,ppsnv=zpsnv,pzs=zzs )
1407  !
1408  isize = SIZE(nindex)
1409  IF (nrank==npio) THEN
1410  ALLOCATE(zsea_full(isize))
1411  ALLOCATE(zwater_full(isize))
1412  ALLOCATE(znature_full(isize))
1413  ALLOCATE(ztown_full(isize))
1414  ALLOCATE(zz0_full(isize))
1415  ALLOCATE(zz0eff_full(isize))
1416  ALLOCATE(zzs_full(isize))
1417  ELSE
1418  ALLOCATE(zsea_full(0))
1419  ALLOCATE(zwater_full(0))
1420  ALLOCATE(znature_full(0))
1421  ALLOCATE(ztown_full(0))
1422  ALLOCATE(zz0_full(0))
1423  ALLOCATE(zz0eff_full(0))
1424  ALLOCATE(zzs_full(0))
1425  ENDIF
1426  CALL gather_and_write_mpi(zsea,zsea_full)
1427  CALL gather_and_write_mpi(zwater,zwater_full)
1428  CALL gather_and_write_mpi(znature,znature_full)
1429  CALL gather_and_write_mpi(ztown,ztown_full)
1430  CALL gather_and_write_mpi(zz0,zz0_full)
1431  CALL gather_and_write_mpi(zz0eff,zz0eff_full)
1432  CALL gather_and_write_mpi(zzs,zzs_full)
1433 
1434  IF (nrank==npio) THEN
1435  WRITE(iluout,'(A32,I4,A3,I4)') ' GRID BOXES CONTAINING SEA : ',count( zsea_full(:) > 0. ),' / ',isize
1436  WRITE(iluout,'(A32,I4,A3,I4)') ' GRID BOXES CONTAINING WATER : ',count( zwater_full(:) > 0. ),' / ',isize
1437  WRITE(iluout,'(A32,I4,A3,I4)') ' GRID BOXES CONTAINING NATURE : ',count( znature_full(:) > 0. ),' / ',isize
1438  WRITE(iluout,'(A32,I4,A3,I4)') ' GRID BOXES CONTAINING TOWN : ',count( ztown_full(:) > 0. ),' / ',isize
1439  WRITE(iluout,*)'ZZ0 = ',zz0_full
1440  WRITE(iluout,*)'ZZ0EFF = ',zz0eff_full
1441  WRITE(iluout,*)'ZZS = ',zzs_full
1442  WRITE(iluout,*)'MINVAL(ZZS) = ',minval(zzs_full),' MAXVAL(ZZS) = ',maxval(zzs_full)
1443  ENDIF
1444  !
1445  DEALLOCATE( zsea )
1446  DEALLOCATE( zwater )
1447  DEALLOCATE( znature )
1448  DEALLOCATE( ztown )
1449  DEALLOCATE( zt2m )
1450  DEALLOCATE( zq2m )
1451  DEALLOCATE( zz0 )
1452  DEALLOCATE( zz0h )
1453  DEALLOCATE( zqs_sea )
1454  DEALLOCATE( zqs_water )
1455  DEALLOCATE( zqs_nature )
1456  DEALLOCATE( zqs_town )
1457  DEALLOCATE( zqs )
1458  DEALLOCATE( zpsng )
1459  DEALLOCATE( zpsnv )
1460  DEALLOCATE( zz0eff )
1461  DEALLOCATE( zzs )
1462  !
1463  IF (nrank==npio) THEN
1464  DEALLOCATE(zsea_full )
1465  DEALLOCATE(zwater_full )
1466  DEALLOCATE(znature_full)
1467  DEALLOCATE(ztown_full )
1468  DEALLOCATE(zz0_full )
1469  DEALLOCATE(zz0eff_full )
1470  DEALLOCATE(zzs_full )
1471  ENDIF
1472  !
1473 ENDIF
1474 !
1475 ! --------------------------------------------------------------------------------------
1476 !
1477 ! 4' Close Gelato specific diagnostic
1478 #if ! defined in_arpege
1479  CALL clsdia()
1480 #endif
1481 !
1482 !
1483 !* 5. Close parallelized I/O
1484 ! ----------------------
1485 !
1486 IF (nrank==npio) THEN
1487  WRITE(iluout,*) ' '
1488  WRITE(iluout,*) ' --------------------------'
1489  WRITE(iluout,*) ' | OFFLINE ENDS CORRECTLY |'
1490  WRITE(iluout,*) ' --------------------------'
1491  WRITE(iluout,*) ' '
1492  CLOSE(iluout)
1493  WRITE(*,*) ' '
1494  WRITE(*,*) ' --------------------------'
1495  WRITE(*,*) ' | OFFLINE ENDS CORRECTLY |'
1496  WRITE(*,*) ' --------------------------'
1497  WRITE(*,*) ' '
1498 ENDIF
1499 !
1500  CALL surfex_deallo_list
1501 !
1502 IF (ALLOCATED(nindex)) DEALLOCATE(nindex)
1503 IF (ALLOCATED(nsize_task)) DEALLOCATE(nsize_task)
1504 !
1505  CALL end_log_mpi
1506 !
1507 IF (lhook) CALL dr_hook('OFFLINE',1,zhook_handle)
1508 !
1509 ! * MPI and OASIS must be finalized after the last DR_HOOK call
1510 !
1511 IF (lxios) THEN
1512 #ifdef WXIOS
1513  CALL xios_context_finalize()
1514 #endif
1515 ENDIF
1516 !
1517  CALL sfx_oasis_end
1518 !
1519 #ifdef SFX_MPI
1520 IF(.NOT. loasis .AND. .NOT. lxios) THEN
1521  CALL mpi_finalize(infompi)
1522 ENDIF
1523 #endif
1524 !
1525 ! --------------------------------------------------------------------------------------
1526 !
1527 END PROGRAM offline
character(len=28) cnamelist
subroutine slope_radiative_effect(PTSTEP, PZENITH, PAZIM, PPS, PTA, PRAIN, PDIR_SW, PLW, PZS, PZS_XY, PSLOPANG, PSLOPAZI, PSURF_TRIANGLE)
subroutine write_header_mnh
subroutine fairme(KREP, KNUMER, CDSTTU)
Definition: fairme.F90:232
integer(kind=jpim) mplusercomm
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:10
character(len=6) csurf_filetype
character(len=28), save cfileout_nc
logical lxios
Definition: modd_xios.F90:41
character(len=6) cforcing_filetype
subroutine init_output_ol_n(YSC)
subroutine sfx_oasis_read_nam(HPROGRAM, PTSTEP_SURF, HINIT)
real, dimension(5) xtime_write
character(len=28), save cfileout_fa
integer, dimension(:), allocatable nm
character(len=28) csurffile
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, TPDATE_END, HATMFILE, HATMFILETYPE, HTEST)
subroutine close_fileout_ol
subroutine diag_surf_atm_n(YSC, HPROGRAM)
real, dimension(:,:), allocatable xqb_dr
subroutine sfx_oasis_send_ol(F, IM, S, U, W, HPROGRAM, KI, PTIMEC, PSTEP_SURF)
real, dimension(:,:), allocatable xqb_run
subroutine write_budget_coupl_rout
subroutine init_index_mpi(DTCO, U, UG, GCP, HPROGRAM, HINIT, HALG, PIO_FRAC, OSHADOWS)
subroutine io_buff_clean
real, save xpi
Definition: modd_csts.F90:43
program offline
Definition: offline.F90:6
subroutine posnam(KULNAM, HDNAML, OFOUND, KLUOUT)
character(len=28), save cfilein_lfi_save
subroutine sfx_oasis_def_ol(IO, U, HPROGRAM, HALG_MPI)
integer nnb_topd_step
character(len=28), save cluout_lfi
character(len=6), dimension(:), allocatable csv
logical ldiag_fa_nocompact
integer, dimension(:), allocatable nyear
character(len=28), save cfilepgd
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:7
real, save xrd
Definition: modd_csts.F90:62
subroutine init_slope_param(UG, PGRID_FULL_PAR, PZS, KI, PLAT)
subroutine close_filein_ol
logical lxios_def_closed
Definition: modd_xios.F90:54
real, dimension(:,:), allocatable xzs_thread
character(len=28), save cfilein_save
integer, dimension(:), allocatable nh
subroutine write_diag_surf_atm_n(YSC, HPROGRAM, HWRITE)
subroutine sunpos(KYEAR, KMONTH, KDAY, PTIME, PLON, PLAT, PTSUN, PZENITH, PAZIMSOL)
Definition: sunpos.F90:8
real, dimension(6) xtime_calc
subroutine sfx_xios_readnam_ol(HNAMELIST)
real, dimension(:,:,:), allocatable xsurf_triangle_thread
real, save xg
Definition: modd_csts.F90:55
subroutine prep_restart_coupl_topd(UG, U, HPROGRAM, KI)
subroutine goto_model(KMODEL)
subroutine surfex_deallo_list
integer, parameter jprb
Definition: parkind1.F90:32
subroutine open_close_bin_asc_forc(HACTION, HFORCING, HACTION2)
subroutine local_slope_param(JPINDX1, JPINDX2)
character(len=6) cprogname
character(len=28), save cluout_nc
subroutine end_log_mpi
character(len=28), save cfilein_fa_save
integer, parameter nundef
character(len=7) csoftware
character(len=6), save cdnomc
subroutine sfx_oasis_init(HNAMELIST, KLOCAL_COMM, HINIT)
subroutine get_surf_var_n(FM, IM, SM, TM, WM, DGO, D, UG, U, USS,
logical lallow_add_dim
Definition: modd_xios.F90:49
subroutine ol_time_interp_atm(KSURF_STEP, KNB_ATM, PTA1, PTA2, PQA1, PQA2, PWIND1, PWIND2, PDIR_SW1, PDIR_SW2, PSCA_SW1, PSCA_SW2, PLW1, PLW2, PSNOW2, PRAIN2, PPS1, PPS2, PCO21, PCO22, PDIR1, PDIR2, PZEN, PSUMZEN)
subroutine flag_update(DIO, DUO, ONOWRITE_CANOPY, OPGD, OPROVAR_TO_DIAG, OSELE
Definition: flag_update.F90:8
type(surfex_t), pointer ysc
subroutine flag_diag_update(FM, IM, SM, TM, WM, DGO, U, SV, OFRAC, ODIAG_GRID, K2M, OSURF_BUDGET, ORAD_BUDGET, OCOEF, OSURF_VARS, KBEQ, KDSTEQ, ODIAG_OCEAN, ODIAG_MISC_SEAICE, OWATER_PROFILE, OSURF_EVAP_BUDGET, OFLOOD, OPGD_ISBA, OCH_NO_FLUX_ISBA, OSURF_MISC_BUDGET_ISBA, OPGD_TEB, OSURF_MISC_BUDGET_TEB)
real, save xrv
Definition: modd_csts.F90:62
subroutine close_namelist(HPROGRAM, KLUNAM)
character(len=28), save cfilepgd_lfi
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)
real, save xday
Definition: modd_csts.F90:45
subroutine read_all_namelists(YSC, HPROGRAM, HINIT, ONAM_READ)
subroutine write_discharge_file(HPROGRAM, HFILE, HFORM, KYEAR, KMONTH, KDAY, KH, KM, PQTOT)
subroutine init_output_nc_n(BDD, CHE, CHN, CHU, DTS, DTT, DTZ, IM
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
subroutine write_surf_atm_n(YSC, HPROGRAM, HWRITE, OLAND_USE)
subroutine sfx_oasis_end
character(len=28), save cfilepgd_fa
integer, dimension(4) ndatestop
integer, dimension(:), allocatable nsize_task
logical lhook
Definition: yomhook.F90:15
character(len=28), save cfileout_lfi
real, dimension(:,:), allocatable xzs_xy_thread
subroutine add_forecast_to_date_surf(KYEAR, KMONTH, KDAY, PSEC)
type(surfex_t), dimension(:), allocatable, target, save ysurf_list
subroutine fandar(KREP, KNUMER, KDATEF)
Definition: fandar.F90:174
integer, dimension(:), allocatable nday
real, dimension(:,:,:), allocatable xslopang_thread
integer, dimension(:), allocatable nindex
real, dimension(:,:,:), allocatable xslopazi_thread
subroutine ol_read_atm_conf(DTCO, U, HGRID, HSURF_FILETYPE, HFORCING_FILETYPE, ODELAYEDSTART_NC, KDATESTOP, PDURATION, PTSTEP_FORC, KNI, KYEAR, KMONTH, KDAY, PTIME, PLAT, PLON, PZS, PZREF, PUREF, KTIMESTARTINDEX)
subroutine init_crodebug(HSNOW_SCHEME)
subroutine surfex_alloc_list(KMODEL)
character(len=4) yalg_mpi
character(len=28), save cfileout
character(len=6) ctimeseries_filetype
subroutine open_namelist(HPROGRAM, KLUNAM, HFILE)
character(len=28), save cfilein
character(len=28), save cfilein_fa
subroutine sfx_oasis_recv_ol(F, IM, S, U, W, HPROGRAM, KI, KSW, PTIMEC, PTSTEP_SURF, PZENITH, PSW_BANDS, PTSRAD, PDIR_ALB, PSCA_ALB, PEMIS, PTSURF)
subroutine compare_orography(DTCO, U, HPROGRAM, OSURFZS, PDELT_ZSMAX)
logical, save lfanocompact
type(xios_context) txios_context
Definition: modd_xios.F90:33
subroutine prep_log_mpi
character(len=28) cpgdfile
character(len=28), save cfilepgd_nc
character(len=28) cprepfile
subroutine wlog_mpi(HLOG, PLOG, KLOG, KLOG2, OLOG)
integer ntimestep
Definition: modd_xios.F90:56
character(len=28), save cfilein_lfi
character(len=28), save cfilein_nc_save
subroutine ol_alloc_atm(KNI, KBANDS, KSCAL)
Definition: ol_alloc_atm.F90:7
integer, dimension(:), allocatable nmonth
subroutine init_surf_landuse_n(DTCO, OREAD_BUDGETC, U, UG, IM, SV, SLT, NDST, 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 write_header_fa(GCP, HGRID, PGRID_PAR, CFILETYPE, HWRITE)
static int count
Definition: memory_hook.c:21
subroutine sfx_xios_setup_ol(YSC, KLUOUT, KYEAR, KMONTH, KDAY, PTIME, PSTEP)
subroutine faitou(KREP, KNUMER, LDNOMM, CDNOMF, CDSTTU, LDERFA, LDIMST, KNIMES, KNBARP, KNBARI, CDNOMC)
Definition: faitou.F90:740
subroutine open_filein_ol
character(len=28), save cfilein_nc
real, dimension(:,:), allocatable xqtot