LMDZ
phys_output_mod.F90
Go to the documentation of this file.
1 ! $Id: phys_output_mod.F90 2380 2015-10-27 15:59:53Z musat $
2 !
3 
7  USE aero_mod, only : naero_spc,name_aero
9  REAL, DIMENSION(nfiles),SAVE :: ecrit_files
10 
11 ! Abderrahmane 12 2007
12 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
13 !!! Ecreture des Sorties du modele dans les fichiers Netcdf :
14 ! histmth.nc : moyennes mensuelles
15 ! histday.nc : moyennes journalieres
16 ! histhf.nc : moyennes toutes les 3 heures
17 ! histins.nc : valeurs instantanees
18 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
19 
20 CONTAINS
21 
22 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
23 !!!!!!!!! Ouverture des fichier et definition des variable de sortie !!!!!!!!
24  !! histbeg, histvert et histdef
25 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
26 
27  SUBROUTINE phys_output_open(rlon,rlat,pim,tabij,ipt,jpt,plon,plat, &
28  jjmp1,nlevstd,clevstd,rlevstd, dtime, ok_veget, &
29  type_ocean, iflag_pbl,iflag_pbl_split,ok_mensuel,ok_journe, &
30  ok_hf,ok_instan,ok_les,ok_ade,ok_aie, read_climoz, &
31  phys_out_filestations, &
32  new_aod, aerosol_couple, flag_aerosol_strat, &
33  pdtphys, paprs, pphis, pplay, lmax_th, ptconv, ptconvth, ivap, &
34  d_t, qx, d_qx, zmasse, ok_sync)
35 
36  USE iophy
37  USE dimphy
38  USE infotrac_phy, ONLY: nqtot, nqo, niadv, tname, ttext
39  USE ioipsl
40  USE phys_cal_mod, only : hour, calend
42  USE aero_mod, only : naero_spc,name_aero
43  !Martin
44  USE surface_data, ONLY : ok_snow
50 #ifdef CPP_XIOS
51  ! ug Pour les sorties XIOS
52  USE wxios
53 #endif
54 
55  IMPLICIT NONE
56  include "clesphys.h"
57  include "thermcell.h"
58 
59  ! ug Nouveaux arguments n\'ecessaires au histwrite_mod:
60  INTEGER, INTENT(IN) :: ivap
61  INTEGER, DIMENSION(klon), INTENT(IN) :: lmax_th
62  LOGICAL, INTENT(IN) :: ok_sync
63  LOGICAL, DIMENSION(klon, klev), INTENT(IN) :: ptconv, ptconvth
64  REAL, INTENT(IN) :: pdtphys
65  REAL, DIMENSION(klon), INTENT(IN) :: pphis
66  REAL, DIMENSION(klon, klev), INTENT(IN) :: pplay, d_t
67  REAL, DIMENSION(klon, klev+1), INTENT(IN) :: paprs
68  REAL, DIMENSION(klon,klev,nqtot), INTENT(IN):: qx, d_qx
69  REAL, DIMENSION(klon, klev), INTENT(IN) :: zmasse
70 
71 
72  REAL,DIMENSION(klon),INTENT(IN) :: rlon
73  REAL,DIMENSION(klon),INTENT(IN) :: rlat
74  INTEGER, INTENT(IN) :: pim
75  INTEGER, DIMENSION(pim) :: tabij
76  INTEGER,DIMENSION(pim), INTENT(IN) :: ipt, jpt
77  REAL,DIMENSION(pim), INTENT(IN) :: plat, plon
78  REAL,DIMENSION(pim,2) :: plat_bounds, plon_bounds
79 
80  INTEGER :: jjmp1
81  INTEGER :: nlevSTD, radpas
82  LOGICAL :: ok_mensuel, ok_journe, ok_hf, ok_instan
83  LOGICAL :: ok_LES,ok_ade,ok_aie,flag_aerosol_strat
84  LOGICAL :: new_aod, aerosol_couple
85  INTEGER, INTENT(IN):: read_climoz ! read ozone climatology
86  ! Allowed values are 0, 1 and 2
87  ! 0: do not read an ozone climatology
88  ! 1: read a single ozone climatology that will be used day and night
89  ! 2: read two ozone climatologies, the average day and night
90  ! climatology and the daylight climatology
91 
92  REAL :: dtime
93  INTEGER :: idayref
94  REAL :: zjulian_start, zjulian
95  REAL, DIMENSION(klev) :: Ahyb, Bhyb, Alt
96  CHARACTER(LEN=4), DIMENSION(nlevSTD) :: clevSTD
97  REAL, DIMENSION(nlevSTD) :: rlevSTD
98  INTEGER :: nsrf, k, iq, iiq, iff, i, j, ilev
99  INTEGER :: naero
100  LOGICAL :: ok_veget
101  INTEGER :: iflag_pbl
102  INTEGER :: iflag_pbl_split
103  CHARACTER(LEN=4) :: bb2
104  CHARACTER(LEN=2) :: bb3
105  CHARACTER(LEN=6) :: type_ocean
106  INTEGER, DIMENSION(nbp_lon*jjmp1) :: ndex2d
107  INTEGER, DIMENSION(nbp_lon*jjmp1*klev) :: ndex3d
108  INTEGER :: imin_ins, imax_ins
109  INTEGER :: jmin_ins, jmax_ins
110  INTEGER, DIMENSION(nfiles) :: phys_out_levmin, phys_out_levmax
111  INTEGER, DIMENSION(nfiles) :: phys_out_filelevels
112  CHARACTER(LEN=20), DIMENSION(nfiles) :: chtimestep = (/ 'Default', 'Default', 'Default', 'Default', 'Default', &
113  'Default', 'Default', 'Default', 'Default' /)
114  LOGICAL, DIMENSION(nfiles) :: phys_out_filekeys
115  LOGICAL, DIMENSION(nfiles) :: phys_out_filestations
116 
117 !!!!!!!!!! stockage dans une region limitee pour chaque fichier !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
118  ! entre [phys_out_lonmin,phys_out_lonmax] et [phys_out_latmin,phys_out_latmax]
119 
120  LOGICAL, DIMENSION(nfiles), SAVE :: phys_out_regfkey = (/ .false., .false., .false., .false., &
121  .false., .false., .false., .false., .false. /)
122  REAL, DIMENSION(nfiles), SAVE :: phys_out_lonmin = (/ -180., -180., -180., -180., &
123  -180., -180., -180., -180., -180. /)
124  REAL, DIMENSION(nfiles), SAVE :: phys_out_lonmax = (/ 180., 180., 180., 180., &
125  180., 180., 180., 180., 180. /)
126  REAL, DIMENSION(nfiles), SAVE :: phys_out_latmin = (/ -90., -90., -90., -90., &
127  -90., -90., -90., -90., -90. /)
128  REAL, DIMENSION(nfiles), SAVE :: phys_out_latmax = (/ 90., 90., 90., 90., &
129  90., 90., 90., 90., 90. /)
130 #ifdef CPP_XIOS
131  ! ug Variables utilis\'ees pour r\'ecup\'erer le calendrier pour xios
132  INTEGER :: x_an, x_mois, x_jour
133  REAL :: x_heure
134  INTEGER :: ini_an, ini_mois, ini_jour
135  REAL :: ini_heure
136 #endif
137 
138  WRITE(lunout,*) 'Debut phys_output_mod.F90'
139  ! Initialisations (Valeurs par defaut
140 
141  IF (.NOT. ALLOCATED(o_trac)) ALLOCATE(o_trac(nqtot))
142  IF (.NOT. ALLOCATED(o_trac_cum)) ALLOCATE(o_trac_cum(nqtot))
147  ALLOCATE(o_dtr_dry(nqtot),o_dtr_vdf(nqtot))
148 
149 
150  levmax = (/ klev, klev, klev, klev, klev, klev, nlevstd, nlevstd, nlevstd /)
151 
152  phys_out_filenames(1) = 'histmth'
153  phys_out_filenames(2) = 'histday'
154  phys_out_filenames(3) = 'histhf6h'
155  phys_out_filenames(4) = 'histhf3h'
156  phys_out_filenames(5) = 'histhf3hm'
157  phys_out_filenames(6) = 'histstn'
158  phys_out_filenames(7) = 'histmthNMC'
159  phys_out_filenames(8) = 'histdayNMC'
160  phys_out_filenames(9) = 'histhfNMC.nc'
161 
162  type_ecri(1) = 'ave(X)'
163  type_ecri(2) = 'ave(X)'
164  type_ecri(3) = 'inst(X)'
165  type_ecri(4) = 'inst(X)'
166  type_ecri(5) = 'ave(X)'
167  type_ecri(6) = 'inst(X)'
168  type_ecri(7) = 'inst(X)'
169  type_ecri(8) = 'inst(X)'
170  type_ecri(9) = 'inst(X)'
171 
172  clef_files(1) = ok_mensuel
173  clef_files(2) = ok_journe
174  clef_files(3) = ok_hf
175  clef_files(4) = ok_instan
176  clef_files(5) = ok_les
177  clef_files(6) = ok_instan
178  clef_files(7) = ok_histnmc(1)
179  clef_files(8) = ok_histnmc(2)
180  clef_files(9) = ok_histnmc(3)
181 
182  !sortir des fichiers "stations" si clef_stations(:)=.TRUE.
183  clef_stations(1) = .false.
184  clef_stations(2) = .false.
185  clef_stations(3) = .false.
186  clef_stations(4) = .false.
187  clef_stations(5) = .false.
188  clef_stations(6) = .false.
189  clef_stations(7) = .false.
190  clef_stations(8) = .false.
191  clef_stations(9) = .false.
192 
193  lev_files(1) = lev_histmth
195  lev_files(3) = lev_histhf
197  lev_files(5) = lev_histles
199  lev_files(7) = levout_histnmc(1)
200  lev_files(8) = levout_histnmc(2)
201  lev_files(9) = levout_histnmc(3)
202 
203  ecrit_files(1) = ecrit_mth
204  ecrit_files(2) = ecrit_day
205  ecrit_files(3) = ecrit_hf
206  ecrit_files(4) = ecrit_ins
207  ecrit_files(5) = ecrit_les
208  ecrit_files(6) = ecrit_ins
209  ecrit_files(7) = freq_outnmc(1)
210  ecrit_files(8) = freq_outnmc(2)
211  ecrit_files(9) = freq_outnmc(3)
212 
213  !! Lectures des parametres de sorties dans physiq.def
214 
215  CALL getin('phys_out_regfkey',phys_out_regfkey)
216  CALL getin('phys_out_lonmin',phys_out_lonmin)
217  CALL getin('phys_out_lonmax',phys_out_lonmax)
218  CALL getin('phys_out_latmin',phys_out_latmin)
219  CALL getin('phys_out_latmax',phys_out_latmax)
220  phys_out_levmin(:)=levmin(:)
221  CALL getin('phys_out_levmin',levmin)
222  phys_out_levmax(:)=levmax(:)
223  CALL getin('phys_out_levmax',levmax)
224  CALL getin('phys_out_filenames',phys_out_filenames)
225  phys_out_filekeys(:)=clef_files(:)
226  CALL getin('phys_out_filekeys',clef_files)
227  phys_out_filestations(:)=clef_stations(:)
228  CALL getin('phys_out_filestations',clef_stations)
229  phys_out_filelevels(:)=lev_files(:)
230  CALL getin('phys_out_filelevels',lev_files)
231  CALL getin('phys_out_filetimesteps',chtimestep)
233  CALL getin('phys_out_filetypes',type_ecri)
234 
236 
237 ! if (ok_all_xml) phys_out_filelevels = 999
238 
239  WRITE(lunout,*)'phys_out_lonmin=',phys_out_lonmin
240  WRITE(lunout,*)'phys_out_lonmax=',phys_out_lonmax
241  WRITE(lunout,*)'phys_out_latmin=',phys_out_latmin
242  WRITE(lunout,*)'phys_out_latmax=',phys_out_latmax
243  WRITE(lunout,*)'phys_out_filenames=',phys_out_filenames
244  WRITE(lunout,*)'phys_out_filetypes=',type_ecri
245  WRITE(lunout,*)'phys_out_filekeys=',clef_files
246  WRITE(lunout,*)'phys_out_filestations=',clef_stations
247  WRITE(lunout,*)'phys_out_filelevels=',lev_files
248 
249 ! A noter pour
250 ! l heure initiale - dans les fichiers histoire hist* - on met comme
251 ! heure de debut soit la vraie heure (pour le 1D) soit 0h (pour le 3D)
252 ! afin d avoir une seule sortie mensuelle par mois lorsque l on tourne
253 ! par annee (IM).
254 !
255  idayref = day_ref
256  IF (klon_glo==1) THEN
257  CALL ymds2ju(annee_ref, 1, idayref, hour, zjulian) !jyg
258  ELSE
259  CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
260  CALL ymds2ju(annee_ref, 1, day_ini, start_time, zjulian_start)
261  END IF
262 
263 #ifdef CPP_XIOS
264  ! ug R\'eglage du calendrier xios
265  !Temps julian => an, mois, jour, heure
266  CALL ju2ymds(zjulian, x_an, x_mois, x_jour, x_heure)
267  CALL ju2ymds(zjulian_start, ini_an, ini_mois, ini_jour, ini_heure)
268  CALL wxios_set_cal(dtime, calend, x_an, x_mois, x_jour, x_heure, ini_an, &
269  ini_mois, ini_jour, ini_heure )
270 #endif
271 
272 !!!!!!!!!!!!!!!!!!!!!!! Boucle sur les fichiers !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
273  ! Appel de histbeg et histvert pour creer le fichier et les niveaux verticaux !!
274  ! Appel des histbeg pour definir les variables (nom, moy ou inst, freq de sortie ..
275 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
276 
277  zdtime_moy = dtime ! Frequence ou l on moyenne
278 
279  ! Calcul des Ahyb, Bhyb et Alt
280  DO k=1,klev
281  ahyb(k)=(ap(k)+ap(k+1))/2.
282  bhyb(k)=(bp(k)+bp(k+1))/2.
283  alt(k)=log(preff/presnivs(k))*8.
284  ENDDO
285  ! if(prt_level.ge.1) then
286  WRITE(lunout,*)'Ap Hybrid = ',ahyb(1:klev)
287  WRITE(lunout,*)'Bp Hybrid = ',bhyb(1:klev)
288  WRITE(lunout,*)'Alt approx des couches pour une haut d echelle de 8km = ',alt(1:klev)
289  ! endif
290 
291  ecrit_files(7) = ecrit_files(1)
292  ecrit_files(8) = ecrit_files(2)
293  ecrit_files(9) = ecrit_files(3)
294 
295  DO iff=1,nfiles
296 
297  ! Calculate ecrit_files for all files
298  IF ( chtimestep(iff).eq.'Default' ) then
299  ! Par defaut ecrit_files = (ecrit_mensuel ecrit_jour ecrit_hf
300  ! ...)*86400.
301  ecrit_files(iff)=ecrit_files(iff)*86400.
302  ELSE IF (chtimestep(iff).eq.'-1') then
303  print*,'ecrit_files(',iff,') < 0 so IOIPSL work on different'
304  print*,'months length'
305  ecrit_files(iff)=-1.
306  else
307  CALL convers_timesteps(chtimestep(iff),dtime,ecrit_files(iff))
308  ENDIF
309 
310  WRITE(lunout,*)'ecrit_files(',iff,')= ',ecrit_files(iff)
311  zoutm(iff) = ecrit_files(iff) ! Frequence ou l on ecrit en seconde
312 
313 
314 #ifdef CPP_XIOS
315 !!! Ouverture de chaque fichier XIOS !!!!!!!!!!!
316  IF (.not. ok_all_xml) then
317  if (prt_level >= 10) then
318  print*,'phys_output_open: call wxios_add_file with phys_out_filenames(iff)=',trim(phys_out_filenames(iff))
319  endif
320  CALL wxios_add_file(phys_out_filenames(iff),chtimestep(iff),lev_files(iff))
321  ENDIF
322 
323 !!! Declaration des axes verticaux de chaque fichier:
324  if (prt_level >= 10) then
325  print*,'phys_output_open: Declare vertical axes for each file'
326  endif
327  if (iff.le.6) then
328  CALL wxios_add_vaxis("presnivs", &
329  levmax(iff) - levmin(iff) + 1, presnivs(levmin(iff):levmax(iff)))
330  CALL wxios_add_vaxis("Ahyb", &
331  levmax(iff) - levmin(iff) + 1, ahyb)
332  CALL wxios_add_vaxis("Bhyb", &
333  levmax(iff) - levmin(iff) + 1, bhyb)
334  CALL wxios_add_vaxis("Alt", &
335  levmax(iff) - levmin(iff) + 1, alt)
336  else
337  ! NMC files
338  CALL wxios_add_vaxis("plev", &
339  levmax(iff) - levmin(iff) + 1, rlevstd(levmin(iff):levmax(iff)))
340  endif
341 #endif
342 
343  IF (clef_files(iff)) THEN
344 !!!!!!!!!!!!!!!!! Traitement dans le cas ou l'on veut stocker sur un domaine limite !!
345 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
346  IF (phys_out_regfkey(iff)) then
347  imin_ins=1
348  imax_ins=nbp_lon
349  jmin_ins=1
350  jmax_ins=jjmp1
351 
352  ! correction abderr
353  do i=1,nbp_lon
354  WRITE(lunout,*)'io_lon(i)=',io_lon(i)
355  IF (io_lon(i).le.phys_out_lonmin(iff)) imin_ins=i
356  IF (io_lon(i).le.phys_out_lonmax(iff)) imax_ins=i+1
357  enddo
358 
359  do j=1,jjmp1
360  WRITE(lunout,*)'io_lat(j)=',io_lat(j)
361  IF (io_lat(j).ge.phys_out_latmin(iff)) jmax_ins=j+1
362  IF (io_lat(j).ge.phys_out_latmax(iff)) jmin_ins=j
363  enddo
364 
365  WRITE(lunout,*)'On stoke le fichier histoire numero ',iff,' sur ', &
366  imin_ins,imax_ins,jmin_ins,jmax_ins
367  WRITE(lunout,*)'longitudes : ', &
368  io_lon(imin_ins),io_lon(imax_ins), &
369  'latitudes : ', &
370  io_lat(jmax_ins),io_lat(jmin_ins)
371 
372  CALL histbeg(phys_out_filenames(iff),nbp_lon,io_lon,jjmp1,io_lat, &
373  imin_ins,imax_ins-imin_ins+1, &
374  jmin_ins,jmax_ins-jmin_ins+1, &
375  itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
376 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
377  !IM fichiers stations
378  else IF (clef_stations(iff)) THEN
379 
380  if (prt_level >= 10) then
381  WRITE(lunout,*)'phys_output_open: iff=',iff,' phys_out_filenames(iff)=',phys_out_filenames(iff)
382  endif
383 
384  CALL histbeg_phy_all(rlon,rlat,pim,tabij,ipt,jpt,plon,plat,plon_bounds,plat_bounds, &
385  phys_out_filenames(iff), &
386  itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
387  else
388  CALL histbeg_phy_all(phys_out_filenames(iff),itau_phy,zjulian,&
389  dtime,nhorim(iff),nid_files(iff))
390  endif
391 
392 #ifndef CPP_IOIPSL_NO_OUTPUT
393  if (iff.le.6) then
394  CALL histvert(nid_files(iff), "presnivs", "Vertical levels", "Pa", &
395  levmax(iff) - levmin(iff) + 1, &
396  presnivs(levmin(iff):levmax(iff)), nvertm(iff),"down")
397 !!!! Composantes de la coordonnee sigma-hybride
398  CALL histvert(nid_files(iff), "Ahyb","Ahyb comp of Hyb Cord ", "Pa", &
399  levmax(iff) - levmin(iff) + 1,ahyb,nvertap(iff))
400 
401  CALL histvert(nid_files(iff), "Bhyb","Bhyb comp of Hyb Cord", " ", &
402  levmax(iff) - levmin(iff) + 1,bhyb,nvertbp(iff))
403 
404  CALL histvert(nid_files(iff), "Alt","Height approx for scale heigh of 8km at levels", "Km", &
405  levmax(iff) - levmin(iff) + 1,alt,nvertalt(iff))
406 
407  else
408  CALL histvert(nid_files(iff), "plev", "pressure", "Pa", &
409  levmax(iff) - levmin(iff) + 1, &
410  rlevstd(levmin(iff):levmax(iff)), nvertm(iff), "down")
411  endif
412 #endif
413 
414  ENDIF ! clef_files
415 
416 !CR: ajout d'une variable eau
417 ! IF (nqtot>=3) THEN
418 
419  IF (nqtot>=nqo+1) THEN
420 ! DO iq=3,nqtot
421  DO iq=nqo+1,nqtot
422  iiq=niadv(iq)
423  o_trac(iq-nqo) = ctrl_out((/ 4, 5, 5, 5, 10, 10, 11, 11, 11 /), &
424  tname(iiq),'Tracer '//ttext(iiq), "-", &
425  (/ '', '', '', '', '', '', '', '', '' /))
426  o_dtr_vdf(iq-nqo) = ctrl_out((/ 4, 7, 7, 7, 10, 10, 11, 11, 11 /), &
427  'd'//trim(tname(iq))//'_vdf', &
428  'Tendance tracer '//ttext(iiq), "-" , &
429  (/ '', '', '', '', '', '', '', '', '' /))
430 
431  o_dtr_the(iq-nqo) = ctrl_out((/ 5, 7, 7, 7, 10, 10, 11, 11, 11 /), &
432  'd'//trim(tname(iq))//'_the', &
433  'Tendance tracer '//ttext(iiq), "-", &
434  (/ '', '', '', '', '', '', '', '', '' /))
435 
436  o_dtr_con(iq-nqo) = ctrl_out((/ 5, 7, 7, 7, 10, 10, 11, 11, 11 /), &
437  'd'//trim(tname(iq))//'_con', &
438  'Tendance tracer '//ttext(iiq), "-", &
439  (/ '', '', '', '', '', '', '', '', '' /))
440 
441  o_dtr_lessi_impa(iq-nqo) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11 /), &
442  'd'//trim(tname(iq))//'_lessi_impa', &
443  'Tendance tracer '//ttext(iiq), "-", &
444  (/ '', '', '', '', '', '', '', '', '' /))
445 
446  o_dtr_lessi_nucl(iq-nqo) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11 /), &
447  'd'//trim(tname(iq))//'_lessi_nucl', &
448  'Tendance tracer '//ttext(iiq), "-", &
449  (/ '', '', '', '', '', '', '', '', '' /))
450 
451  o_dtr_insc(iq-nqo) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11 /), &
452  'd'//trim(tname(iq))//'_insc', &
453  'Tendance tracer '//ttext(iiq), "-", &
454  (/ '', '', '', '', '', '', '', '', '' /))
455 
456  o_dtr_bcscav(iq-nqo) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11 /), &
457  'd'//trim(tname(iq))//'_bcscav', &
458  'Tendance tracer '//ttext(iiq), "-", &
459  (/ '', '', '', '', '', '', '', '', '' /))
460 
461  o_dtr_evapls(iq-nqo) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11 /), &
462  'd'//trim(tname(iq))//'_evapls', &
463  'Tendance tracer '//ttext(iiq), "-", &
464  (/ '', '', '', '', '', '', '', '', '' /))
465 
466  o_dtr_ls(iq-nqo) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11 /), &
467  'd'//trim(tname(iq))//'_ls', &
468  'Tendance tracer '//ttext(iiq), "-", &
469  (/ '', '', '', '', '', '', '', '', '' /))
470 
471  o_dtr_trsp(iq-nqo) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11 /), &
472  'd'//trim(tname(iq))//'_trsp', &
473  'Tendance tracer '//ttext(iiq), "-", &
474  (/ '', '', '', '', '', '', '', '', '' /))
475 
476  o_dtr_sscav(iq-nqo) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11 /), &
477  'd'//trim(tname(iq))//'_sscav', &
478  'Tendance tracer '//ttext(iiq), "-", &
479  (/ '', '', '', '', '', '', '', '', '' /))
480 
481  o_dtr_sat(iq-nqo) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11 /), &
482  'd'//trim(tname(iq))//'_sat', &
483  'Tendance tracer '//ttext(iiq), "-", &
484  (/ '', '', '', '', '', '', '', '', '' /))
485 
486  o_dtr_uscav(iq-nqo) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11 /), &
487  'd'//trim(tname(iq))//'_uscav', &
488  'Tendance tracer '//ttext(iiq), "-", &
489  (/ '', '', '', '', '', '', '', '', '' /))
490 
491  o_dtr_dry(iq-nqo) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11 /), &
492  'cum'//'d'//trim(tname(iq))//'_dry', &
493  'tracer tendency dry deposition'//ttext(iiq), "-", &
494  (/ '', '', '', '', '', '', '', '', '' /))
495 
496  o_trac_cum(iq-nqo) = ctrl_out((/ 3, 4, 10, 10, 10, 10, 11, 11, 11 /), &
497  'cum'//tname(iiq),&
498  'Cumulated tracer '//ttext(iiq), "-", &
499  (/ '', '', '', '', '', '', '', '', '' /))
500  ENDDO
501  ENDIF
502 
503 
504  ENDDO ! iff
505 
506  ! Updated write frequencies due to phys_out_filetimesteps.
507  ! Write frequencies are now in seconds.
508  ecrit_mth = ecrit_files(1)
509  ecrit_day = ecrit_files(2)
510  ecrit_hf = ecrit_files(3)
511  ecrit_ins = ecrit_files(4)
512  ecrit_les = ecrit_files(5)
513  ecrit_ins = ecrit_files(6)
514 
515  if (prt_level >= 10) then
516  WRITE(lunout,*)'swaero_diag=',swaero_diag
517  WRITE(lunout,*)'phys_output_open: ends here'
518  endif
519 
520  end SUBROUTINE phys_output_open
521 
522 
523 
524  SUBROUTINE convers_timesteps(str,dtime,timestep)
526  use ioipsl
527  USE phys_cal_mod
529  USE print_control_mod, ONLY: lunout
530 
531  IMPLICIT NONE
532 
533  CHARACTER(LEN=20) :: str
534  CHARACTER(LEN=10) :: type
535  INTEGER :: ipos,il
536  real :: ttt,xxx,timestep,dayseconde,dtime
537  parameter(dayseconde=86400.)
538 
539  ipos=scan(str,'0123456789.',.true.)
540  !
541  il=len_trim(str)
542  WRITE(lunout,*) "ipos = ", ipos
543  WRITE(lunout,*) "il = ", il
544  if (ipos == 0) call abort_physic("convers_timesteps", "bad str", 1)
545  read(str(1:ipos),*) ttt
546  WRITE(lunout,*)ttt
547  type=str(ipos+1:il)
548 
549 
550  IF ( il == ipos ) then
551  type='day'
552  endif
553 
554  IF ( type == 'day'.or.type == 'days'.or.type == 'jours'.or.type == 'jour' ) timestep = ttt * dayseconde
555  IF ( type == 'mounths'.or.type == 'mth'.or.type == 'mois' ) then
556  WRITE(lunout,*)'annee_ref,day_ref mon_len',annee_ref,day_ref,mth_len
557  timestep = ttt * dayseconde * mth_len
558  endif
559  IF ( type == 'hours'.or.type == 'hr'.or.type == 'heurs') timestep = ttt * dayseconde / 24.
560  IF ( type == 'mn'.or.type == 'minutes' ) timestep = ttt * 60.
561  IF ( type == 's'.or.type == 'sec'.or.type == 'secondes' ) timestep = ttt
562  IF ( type == 'TS' ) timestep = ttt * dtime
563 
564  WRITE(lunout,*)'type = ',type
565  WRITE(lunout,*)'nb j/h/m = ',ttt
566  WRITE(lunout,*)'timestep(s)=',timestep
567 
568  END SUBROUTINE convers_timesteps
569 
570 END MODULE phys_output_mod
571 
572 
type(ctrl_out), dimension(:), allocatable, save o_dtr_sat
type(ctrl_out), dimension(:), allocatable, save o_dtr_vdf
character(len=10) calend
character(len=20), dimension(nfiles), save phys_out_filenames
!$Id ***************************************!ECRITURE DU pphis CALL zmasse
Definition: write_histrac.h:11
!$Id zjulian!correction pour l heure initiale!jyg!jyg CALL ymds2ju(annee_ref, 1, day_ref, hour, zjulian)!jyg CALL histbeg_phy("histrac"
real, dimension(:), allocatable, save io_lat
Definition: iophy.F90:8
integer, dimension(nfiles), save nid_files
!$Id ok_orolf LOGICAL ok_limitvrai LOGICAL ok_all_xml INTEGER iflag_ener_conserv REAL solaire RCFC12 RCFC12_act CFC12_ppt!IM ajout CFMIP2 CMIP5 LOGICAL ok_4xCO2atm RCFC12_per CFC12_ppt_per!OM correction du bilan d eau global!OM Correction sur precip KE REAL cvl_corr!OM Fonte calotte dans bilan eau LOGICAL ok_lic_melt!IM simulateur ISCCP INTEGER overlap!IM seuils cdrh REAL cdhmax!IM param stabilite s terres et en dehors REAL f_ri_cd_min!IM MAFo pmagic evap0!Frottement au f_cdrag_oce REAL f_z0qh_oce REAL z0h_seaice INTEGER iflag_z0_oce!Rugoro Real z0min!IM lev_histmth INTEGER lev_histdayNMC Integer lev_histins
Definition: clesphys.h:46
!$Id preff
Definition: comvert.h:8
type(ctrl_out), dimension(:), allocatable, save o_dtr_sscav
!$Header!integer nvarmx dtime
Definition: gradsdef.h:20
character(len=20), dimension(nfiles), save phys_out_filetypes
real, dimension(nfiles), save zoutm
subroutine phys_output_open(rlon, rlat, pim, tabij, ipt, jpt, plon, plat, jjmp1, nlevSTD, clevSTD, rlevSTD, dtime, ok_veget, type_ocean, iflag_pbl, iflag_pbl_split, ok_mensuel, ok_journe, ok_hf, ok_instan, ok_LES, ok_ade, ok_aie, read_climoz, phys_out_filestations, new_aod, aerosol_couple, flag_aerosol_strat, pdtphys, paprs, pphis, pplay, lmax_th, ptconv, ptconvth, ivap, d_t, qx, d_qx, zmasse, ok_sync)
integer, save klon_glo
integer, save klev
Definition: dimphy.F90:7
!$Id iflag_pbl_split common compbl iflag_pbl
Definition: compbl.h:7
!$Id ok_orolf LOGICAL ok_limitvrai LOGICAL ok_all_xml INTEGER iflag_ener_conserv REAL solaire RCFC12 RCFC12_act CFC12_ppt!IM ajout CFMIP2 CMIP5 LOGICAL ok_4xCO2atm RCFC12_per CFC12_ppt_per!OM correction du bilan d eau global!OM Correction sur precip KE REAL cvl_corr!OM Fonte calotte dans bilan eau LOGICAL ok_lic_melt!IM simulateur ISCCP INTEGER overlap!IM seuils cdrh REAL cdhmax!IM param stabilite s terres et en dehors REAL f_ri_cd_min!IM MAFo pmagic evap0!Frottement au f_cdrag_oce REAL f_z0qh_oce REAL z0h_seaice INTEGER iflag_z0_oce!Rugoro Real z0min!IM lev_histday
Definition: clesphys.h:46
type(ctrl_out), dimension(:), allocatable, save o_dtr_lessi_impa
integer, save mth_len
type(ctrl_out), dimension(:), allocatable, save o_dtr_con
!$Id itau_phy
Definition: temps.h:15
type(ctrl_out), dimension(:), allocatable, save o_dtr_uscav
real, save hour
type(ctrl_out), dimension(:), allocatable, save o_dtr_bcscav
type(ctrl_out), dimension(:), allocatable, save o_dtr_trsp
!$Id && day_ini
Definition: temps.h:15
integer, dimension(nfiles), save nhorim
type(ctrl_out), dimension(:), allocatable, save o_dtr_dry
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
Definition: calcul_STDlev.h:26
type(ctrl_out), dimension(:), allocatable, save o_trac_cum
integer, dimension(:), allocatable, save niadv
logical, dimension(nfiles), save clef_stations
!$Id zjulian!correction pour l heure initiale!jyg!jyg CALL nid_tra CALL histvert(nid_tra,"presnivs","Vertical levels","Pa", klev, presnivs, nvert,"down") zsto
!$Id day_ref
Definition: temps.h:15
integer, dimension(nfiles), save levmin
integer, save nqtot
Definition: infotrac_phy.F90:8
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL pplay
Definition: calcul_STDlev.h:26
!FH On elimine toutes les clefs physiques dans la dynamique prt_level
subroutine phys_output_write(itap, pdtphys, paprs, pphis, pplay, lmax_th, aerosol_couple, ok_ade, ok_aie, ivap, new_aod, ok_sync, ptconv, read_climoz, clevSTD, ptconvth, d_t, qx, d_qx, zmasse, flag_aerosol, flag_aerosol_strat, ok_cdnc)
integer, dimension(nfiles), save levmax
!$Header!integer nvarmx parameter(nfmx=10, imx=200, jmx=150, lmx=200, nvarmx=1000) real xd(imx
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL &zphi geo500!IM on interpole a chaque pas de temps le paprs
type(ctrl_out), dimension(:), allocatable, save o_dtr_insc
subroutine convers_timesteps(str, dtime, timestep)
character(len=23), dimension(:), allocatable, save ttext
type(ctrl_out), dimension(:), allocatable, save o_dtr_evapls
real, dimension(:), allocatable, save io_lon
Definition: iophy.F90:9
c c zjulian c cym CALL iim cym klev jjmp1
Definition: ini_bilKP_ave.h:24
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
character(len=20), dimension(:), allocatable, save tname
character(len=20), dimension(nfiles), save type_ecri
real, dimension(:), allocatable, save ap
type(ctrl_out), dimension(:), allocatable, save o_dtr_lessi_nucl
integer, dimension(nfiles), save nvertap
integer, parameter nfiles
!$Id zjulian!correction pour l heure initiale!jyg!jyg CALL pdtphys
Definition: ini_histrac.h:11
type(ctrl_out), dimension(:), allocatable, save o_dtr_ls
logical, save ok_snow
real, dimension(nfiles), save ecrit_files
character(len=20), dimension(nfiles), save type_ecri_files
integer, parameter naero_spc
Definition: aero_mod.F90:48
subroutine abort_physic(modname, message, ierr)
Definition: abort_physic.F90:3
character(len=7), dimension(naero_spc), parameter name_aero
Definition: aero_mod.F90:51
integer, dimension(nfiles), save nvertbp
integer, dimension(nfiles), save lev_files
c c zjulian c cym CALL iim cym klev iim cym jjmp1 cym On stoke le fichier bilKP instantanne s jmax_ins print On stoke le fichier bilKP instantanne s s cym cym nid_bilKPins ENDIF c cIM BEG c cIM cf AM BEG region cym CALL histbeg("histbilKP_ins", iim, zx_lon(:, 1), cym.jjmp1, zx_lat(1,:), cym.imin_ins, imax_ins-imin_ins+1, cym.jmin_ins, jmax_ins-jmin_ins+1, cym.itau_phy, zjulian, dtime, cym.nhori, nid_bilKPins) CALL histbeg_phy("histbilKP_ins"
logical, dimension(nfiles), save clef_files
!$Id ok_orolf LOGICAL ok_limitvrai LOGICAL ok_all_xml INTEGER iflag_ener_conserv REAL solaire RCFC12 RCFC12_act CFC12_ppt!IM ajout CFMIP2 CMIP5 LOGICAL ok_4xCO2atm RCFC12_per CFC12_ppt_per!OM correction du bilan d eau global!OM Correction sur precip KE REAL cvl_corr!OM Fonte calotte dans bilan eau LOGICAL ok_lic_melt!IM simulateur ISCCP INTEGER overlap!IM seuils cdrh REAL cdhmax!IM param stabilite s terres et en dehors REAL f_ri_cd_min!IM MAFo pmagic evap0!Frottement au f_cdrag_oce REAL f_z0qh_oce REAL z0h_seaice INTEGER iflag_z0_oce!Rugoro Real z0min!IM lev_histhf
Definition: clesphys.h:46
real, dimension(:), allocatable, save bp
!$Id start_time
Definition: temps.h:15
integer, dimension(nfiles), save nvertalt
type(ctrl_out), dimension(:), allocatable, save o_trac
Definition: dimphy.F90:1
integer, save nqo
Definition: iophy.F90:4
integer, dimension(nfiles), save nvertm
real, dimension(:), allocatable, save presnivs
!$Id annee_ref
Definition: temps.h:15
!$Header!gestion des impressions de sorties et de débogage la sortie standard prt_level COMMON comprint lunout
Definition: iniprint.h:7
type(ctrl_out), dimension(:), allocatable, save o_dtr_the